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
This commit is contained in:
Jonathan Chen 2000-10-18 03:25:13 +00:00
parent c33f14430f
commit 0db7e66cdc
10 changed files with 3666 additions and 599 deletions

View File

@ -146,6 +146,9 @@ dev/buslogic/bt_isa.c optional bt isa
dev/buslogic/bt_mca.c optional bt mca
dev/buslogic/bt_pci.c optional bt pci
dev/cardbus/cardbus.c optional cardbus
dev/cardbus/cardbus_cis.c optional cardbus
dev/pccbb/pccbb_if.m optional cardbus
dev/pccbb/pccbb_if.m optional pccbb
dev/ccd/ccd.c count ccd
dev/cs/if_cs.c optional cs
#dev/dpt/dpt_control.c optional dpt
@ -240,10 +243,12 @@ dev/mly/mly_pci.c optional mly
dev/musycc/musycc.c optional musycc
dev/null/null.c standard
dev/pccard/card_if.m optional card
dev/pccard/card_if.m optional cardbus
dev/pccard/card_if.m optional pccard
dev/pccard/pccard.c optional pccard
dev/pccard/pccard_cis.c optional pccard
dev/pccard/pccard_cis_quirks.c optional pccard
dev/pccard/power_if.m optional pccbb
dev/pccard/power_if.m optional pccard
dev/pcic/i82365.c optional pcic pccard
dev/pcic/i82365_isa.c optional pcic pccard
@ -958,7 +963,7 @@ pci/isp_pci.c optional isp
pci/meteor.c count meteor pci
pci/ncr.c optional ncr
pci/ohci_pci.c optional ohci
pci/pccbb.c optional pccbb cardbus
dev/pccbb/pccbb.c optional pccbb
pci/pci.c count pci
pci/pci_compat.c optional pci compat_oldpci \
warning "Old PCI driver compatability shims present."

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,477 @@
/*
* 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$
*/
/*
* CIS Handling for the Cardbus Bus
*/
#define CARDBUS_DEBUG
#include <sys/param.h>
#include <sys/systm.h>
#include <sys/kernel.h>
#include <sys/bus.h>
#include <machine/bus.h>
#include <machine/resource.h>
#include <sys/rman.h>
#include <pci/pcivar.h>
#include <dev/cardbus/cardbusreg.h>
#include <dev/cardbus/cardbus_cis.h>
#include "pccbb_if.h"
#if defined CARDBUS_DEBUG
#define STATIC
#define DPRINTF(a) printf a
#define DEVPRINTF(x) device_printf x
#else
#define STATIC static
#define DPRINTF(a)
#define DEVPRINTF(x)
#endif
#if !defined(lint)
static const char rcsid[] =
"$FreeBSD$";
#endif
struct tupleinfo;
static int decode_tuples(device_t dev, device_t child,
u_int8_t *tuples, int len);
static int cardbus_read_exrom_cis(device_t dev, struct resource *res,
int cis, u_int8_t* tuple, int len);
static int cardbus_read_tuples_conf(device_t dev, device_t child,
u_int32_t cis_ptr, u_int8_t *tuples,
int len);
static int cardbus_read_tuples_mem(device_t dev, device_t child, int space,
u_int32_t cis_ptr, u_int8_t *tuples,
int len);
static int cardbus_read_tuples(device_t dev, device_t child, u_int8_t *tuples,
int len);
#define DECODE_PROTOTYPE(NAME) static int decode_tuple_ ## NAME \
(device_t dev, device_t child, int id, int len, \
u_int8_t *buff, struct tupleinfo *info)
DECODE_PROTOTYPE(generic);
DECODE_PROTOTYPE(bar);
DECODE_PROTOTYPE(linktarget);
DECODE_PROTOTYPE(vers_1);
DECODE_PROTOTYPE(manfid);
DECODE_PROTOTYPE(funcid);
DECODE_PROTOTYPE(funce);
DECODE_PROTOTYPE(end);
DECODE_PROTOTYPE(unhandled);
static struct tupleinfo {
u_int8_t id;
char* name;
int (*func)(device_t dev, device_t child, int id, int len,
u_int8_t *buff, struct tupleinfo *info);
} tupleinfo[] = {
#define MAKETUPLE(NAME,FUNC) { CISTPL_ ## NAME, #NAME, decode_tuple_ ## FUNC }
MAKETUPLE(NULL, generic),
MAKETUPLE(DEVICE, generic),
MAKETUPLE(LONG_LINK_CB, unhandled),
MAKETUPLE(INDIRECT, unhandled),
MAKETUPLE(CONFIG_CB, generic),
MAKETUPLE(CFTABLE_ENTRY_CB, generic),
MAKETUPLE(LONGLINK_MFC, unhandled),
MAKETUPLE(BAR, bar),
MAKETUPLE(PWR_MGMNT, generic),
MAKETUPLE(EXTDEVICE, generic),
MAKETUPLE(CHECKSUM, generic),
MAKETUPLE(LONGLINK_A, unhandled),
MAKETUPLE(LONGLINK_C, unhandled),
MAKETUPLE(LINKTARGET, linktarget),
MAKETUPLE(NO_LINK, generic),
MAKETUPLE(VERS_1, vers_1),
MAKETUPLE(ALTSTR, generic),
MAKETUPLE(DEVICE_A, generic),
MAKETUPLE(JEDEC_C, generic),
MAKETUPLE(JEDEC_A, generic),
MAKETUPLE(CONFIG, generic),
MAKETUPLE(CFTABLE_ENTRY, generic),
MAKETUPLE(DEVICE_OC, generic),
MAKETUPLE(DEVICE_OA, generic),
MAKETUPLE(DEVICE_GEO, generic),
MAKETUPLE(DEVICE_GEO_A, generic),
MAKETUPLE(MANFID, manfid),
MAKETUPLE(FUNCID, funcid),
MAKETUPLE(FUNCE, funce),
MAKETUPLE(SWIL, generic),
MAKETUPLE(VERS_2, generic),
MAKETUPLE(FORMAT, generic),
MAKETUPLE(GEOMETRY, generic),
MAKETUPLE(BYTEORDER, generic),
MAKETUPLE(DATE, generic),
MAKETUPLE(BATTERY, generic),
MAKETUPLE(ORG, generic),
MAKETUPLE(END, end),
#undef MAKETUPLE
};
static char* funcnames[] = {
"Multi-Functioned",
"Memory",
"Serial Port",
"Parallel Port",
"Fixed Disk",
"Video Adaptor",
"Network Adaptor",
"AIMS",
"SCSI",
"Security"
};
DECODE_PROTOTYPE(generic)
{
#ifdef CARDBUS_DEBUG
int i;
if (info)
printf ("TUPLE: %s [%d]:", info->name, len);
else
printf ("TUPLE: Unknown(0x%02x) [%d]:", id, len);
for (i = 0; i < len; i++) {
if (i % 0x10 == 0 && len > 0x10)
printf ("\n 0x%02x:", i);
printf (" %02x", buff[i]);
}
printf ("\n");
#endif
return 0;
}
DECODE_PROTOTYPE(linktarget)
{
if (len != 3 || buff[0] != 'C' || buff[1] != 'I' || buff[2] != 'S') {
printf("Invalid data for CIS Link Target!\n");
decode_tuple_generic(dev, child, id, len, buff, info);
return EINVAL;
}
return 0;
}
DECODE_PROTOTYPE(vers_1)
{
int i;
printf("Product version: %d.%d\n", buff[0], buff[1]);
printf("Product name: ");
for (i = 2; i < len; i++) {
if (buff[i] == '\0')
printf (" | ");
else if (buff[i] == 0xff)
break;
else
printf("%c", buff[i]);
}
printf("\n");
return 0;
}
DECODE_PROTOTYPE(funcid)
{
int i;
int numnames = sizeof(funcnames)/sizeof(funcnames[0]);
printf("Functions: ");
for(i = 0; i < len; i++) {
if (buff[i] < numnames)
printf ("%s", funcnames[buff[i]]);
else
printf ("Unknown(%d)", buff[i]);
if (i < len-1) printf(", ");
}
printf ("\n");
return 0;
}
DECODE_PROTOTYPE(manfid)
{
int i;
printf ("Manufacturer ID: ");
for (i = 0; i < len; i++)
printf("%02x", buff[i]);
printf("\n");
return 0;
}
DECODE_PROTOTYPE(funce)
{
int i;
printf ("Function Extension: ");
for (i = 0; i < len; i++)
printf("%02x", buff[i]);
printf("\n");
return 0;
}
DECODE_PROTOTYPE(bar)
{
if (len != 6) {
printf ("*** ERROR *** BAR length not 6 (%d)\n", len);
return EINVAL;
} else {
int type;
int reg;
u_int32_t bar;
u_int32_t start, len;
struct resource *res;
reg = *(u_int16_t*)buff;
len = *(u_int32_t*)(buff+2);
if (reg & TPL_BAR_REG_AS) {
type = SYS_RES_IOPORT;
} else {
type = SYS_RES_MEMORY;
}
bar = (reg & TPL_BAR_REG_ASI_MASK) - 1;
if (bar < 0 || bar > 6) {
device_printf(dev, "Invalid BAR number: %02x(%02x)\n",
reg, bar);
return EINVAL;
}
bar = CARDBUS_BASE0_REG + bar * 4;
DEVPRINTF((dev, "Opening BAR: type=%s, bar=%02x, len=%04x\n",
(type==SYS_RES_MEMORY)?"MEM":"IO", bar, len));
res = bus_generic_alloc_resource(child, child, type, &reg, 0,
~0, len, rman_make_alignment_flags(len) | RF_ACTIVE);
if (res == NULL) {
device_printf(dev, "Cannot allocate BAR %02x\n", reg);
} else {
start = rman_get_start(res);
if (reg == CARDBUS_ROM_REG) start |= 1;
pci_write_config(child, reg, start, 4);
}
}
return 0;
}
DECODE_PROTOTYPE(unhandled)
{
printf ("TUPLE: %s [%d] is unhandled! Bailing...", info->name, len);
return -1;
}
DECODE_PROTOTYPE(end)
{
return -1;
}
static int decode_tuples(device_t dev, device_t child,
u_int8_t *tuples, int len)
{
int ret = 0;
if (CISTPL_LINKTARGET != *tuples) {
device_printf(dev, "CIS does not start with link target\n");
return EINVAL;
}
do {
int i;
int numtupleids = sizeof(tupleinfo)/sizeof(tupleinfo[0]);
for (i = 0; i < numtupleids; i++) {
if (tuples[0] == tupleinfo[i].id) {
ret = tupleinfo[i].func(dev, child, tuples[0],
tuples[1], tuples+2,
&tupleinfo[i]);
break;
}
}
if (i == numtupleids)
ret = decode_tuple_generic(dev, child, tuples[0],
tuples[1], tuples+2, NULL);
len -= (tuples[1]+2);
tuples += tuples[1]+2;
} while (len > 0 && ret == 0);
if (ret < 0) return 0;
else if (ret != 0) return ret;
else {
device_printf(dev, "CIS too long or END not encountered!\n");
return EFBIG;
}
}
static int
cardbus_read_exrom_cis(device_t dev, struct resource *res, int cis,
u_int8_t* tuple, int len)
{
#define READROM(rom, type, offset) \
(*((u_int ## type ##_t *)(((unsigned char*)rom) + offset)))
u_int32_t addr = 0; /* offset of current rom image */
int romnum = 0;
unsigned char *data;
u_int32_t imagesize;
unsigned char *image;
int imagenum;
image = (unsigned char*)rman_get_virtual(res);
imagenum = CARDBUS_CIS_ASI_ROM_IMAGE(cis);
do {
if (READROM(image, 16, CARDBUS_EXROM_SIGNATURE) != 0xaa55) {
device_printf (dev, "Bad header in rom %d: %04x\n",
romnum, *(u_int16_t*)(image +
CARDBUS_EXROM_SIGNATURE));
return ENXIO;
}
data = image + READROM(image, 16, CARDBUS_EXROM_DATA_PTR);
imagesize = READROM(data, 16, CARDBUS_EXROM_DATA_IMAGE_LENGTH);
if(imagesize == 0)
/*
* XXX some ROMs seem to have this as zero,
* can we assume this means 1 block?
*/
imagesize = 1;
imagesize <<= 9;
if (imagenum == romnum) {
romnum = -1;
memcpy(tuple, image+CARDBUS_CIS_ADDR(cis), len);
return 0;
}
addr += imagesize;
romnum++;
} while ((READROM(data, 8, CARDBUS_EXROM_DATA_INDICATOR) & 0x80) == 0);
device_printf(dev, "Cannot read CIS: Not enough images of rom\n");
return ENOENT;
#undef READROM
}
static int
cardbus_read_tuples_conf(device_t dev, device_t child, u_int32_t cis_ptr,
u_int8_t *tuples, int len)
{
int i, j;
DEVPRINTF((dev, "reading CIS data from configuration space\n"));
for (i = cis_ptr, j = 0; i < len; i += 4) {
u_int32_t e = pci_read_config(child, i, 4);
tuples[j] = 0xff & e;
e >>= 8;
tuples[j + 1] = 0xff & e;
e >>= 8;
tuples[j + 2] = 0xff & e;
e >>= 8;
tuples[j + 3] = 0xff & e;
j += 4;
}
return 0;
}
static int
cardbus_read_tuples_mem(device_t dev, device_t child, int space,
u_int32_t cis_ptr, u_int8_t *tuples, int len)
{
struct resource *mem;
int rid;
int ret;
if(space == CARDBUS_CIS_ASI_ROM) {
rid = CARDBUS_ROM_REG;
DEVPRINTF((dev, "reading CIS data from ROM\n"));
} else {
rid = CARDBUS_BASE0_REG + (space - 1) * 4;
DEVPRINTF((dev, "reading CIS data from BAR%d\n", space - 1));
}
mem = bus_alloc_resource(child, SYS_RES_MEMORY, &rid, 0, ~0,
1, RF_ACTIVE);
if (mem == NULL) {
device_printf(dev, "Failed to get memory for CIS reading\n");
return ENOMEM;
}
if(space == CARDBUS_CIS_ASI_ROM) {
int s;
s = splhigh();
ret = cardbus_read_exrom_cis(dev, mem, cis_ptr, tuples, len);
splx(s);
} else {
/* XXX byte order? */
memcpy(tuples, (unsigned char*)rman_get_virtual(mem)+cis_ptr,
len);
ret = 0;
}
bus_release_resource(child, SYS_RES_MEMORY, rid, mem);
return ret;
}
static int
cardbus_read_tuples(device_t dev, device_t child, u_int8_t *tuples, int len)
{
u_int32_t cis_ptr = pci_read_config(child, CARDBUS_CIS_REG, 4);
int cardbus_space = cis_ptr & CARDBUS_CIS_ASIMASK;
int ret = 0;
cis_ptr = cis_ptr & CARDBUS_CIS_ADDRMASK;
switch(cardbus_space) {
case CARDBUS_CIS_ASI_TUPLE:
ret = cardbus_read_tuples_conf(dev, child, cis_ptr, tuples,
len);
break;
case CARDBUS_CIS_ASI_BAR0:
case CARDBUS_CIS_ASI_BAR1:
case CARDBUS_CIS_ASI_BAR2:
case CARDBUS_CIS_ASI_BAR3:
case CARDBUS_CIS_ASI_BAR4:
case CARDBUS_CIS_ASI_BAR5:
case CARDBUS_CIS_ASI_ROM:
ret = cardbus_read_tuples_mem(dev, child, cardbus_space,
cis_ptr, tuples, len);
break;
default:
device_printf(dev, "Unable to read CIS: Unknown space: %d\n",
cardbus_space);
ret = EINVAL;
}
return ret;
}
int
cardbus_do_cis(device_t dev, device_t child)
{
u_int8_t tupledata[MAXTUPLESIZE];
int ret;
bzero(tupledata, MAXTUPLESIZE);
ret = cardbus_read_tuples(dev, child, tupledata, MAXTUPLESIZE);
if (ret != 0) return ret;
return decode_tuples(dev, child, tupledata, MAXTUPLESIZE);
}

View File

@ -0,0 +1,99 @@
/*
* 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$
*/
/*
* Cardbus CIS definitions
*/
int cardbus_do_cis(device_t dev, device_t child);
#define MAXTUPLESIZE 0x400
/* CIS TUPLES */
#define CISTPL_NULL 0x00
#define CISTPL_DEVICE 0x01
#define CISTPL_LONG_LINK_CB 0x02
#define CISTPL_INDIRECT 0x03
#define CISTPL_CONFIG_CB 0x04
#define CISTPL_CFTABLE_ENTRY_CB 0x05
#define CISTPL_LONGLINK_MFC 0x06
#define CISTPL_BAR 0x07
#define CISTPL_PWR_MGMNT 0x08
#define CISTPL_EXTDEVICE 0x09
#define CISTPL_CHECKSUM 0x10
#define CISTPL_LONGLINK_A 0x11
#define CISTPL_LONGLINK_C 0x12
#define CISTPL_LINKTARGET 0x13
#define CISTPL_NO_LINK 0x14
#define CISTPL_VERS_1 0x15
#define CISTPL_ALTSTR 0x16
#define CISTPL_DEVICE_A 0x17
#define CISTPL_JEDEC_C 0x18
#define CISTPL_JEDEC_A 0x19
#define CISTPL_CONFIG 0x1A
#define CISTPL_CFTABLE_ENTRY 0x1B
#define CISTPL_DEVICE_OC 0x1C
#define CISTPL_DEVICE_OA 0x1D
#define CISTPL_DEVICE_GEO 0x1E
#define CISTPL_DEVICE_GEO_A 0x1F
#define CISTPL_MANFID 0x20
#define CISTPL_FUNCID 0x21
#define CISTPL_FUNCE 0x22
#define CISTPL_SWIL 0x23
#define CISTPL_VERS_2 0x40
#define CISTPL_FORMAT 0x41
#define CISTPL_GEOMETRY 0x42
#define CISTPL_BYTEORDER 0x43
#define CISTPL_DATE 0x44
#define CISTPL_BATTERY 0x45
#define CISTPL_ORG 0x46
#define CISTPL_END 0xFF
/* BAR */
#define TPL_BAR_REG_ASI_MASK 0x07
#define TPL_BAR_REG_AS 0x08
/* CISTPL_FUNC */
#define TPL_FUNC_MF 0 /* multi function tuple */
#define TPL_FUNC_MEM 1 /* memory */
#define TPL_FUNC_SERIAL 2 /* serial, including modem and fax */
#define TPL_FUNC_PARALLEL 3 /* parallel, including printer and SCSI */
#define TPL_FUNC_DISK 4 /* Disk */
#define TPL_FUNC_VIDEO 5 /* Video Adaptor */
#define TPL_FUNC_LAN 6 /* LAN Adaptor */
#define TPL_FUNC_AIMS 7 /* Auto Inclement Mass Strages */
/* TPL_FUNC_LAN */
#define TPL_FUNCE_LAN_TECH 1 /* technology */
#define TPL_FUNCE_LAN_SPEED 2 /* speed */
#define TPL_FUNCE_LAN_MEDIA 2 /* which media do you use? */
#define TPL_FUNCE_LAN_NID 4 /* node id (address) */
#define TPL_FUNCE_LAN_CONN 5 /* connector type (shape) */

View File

@ -1,105 +1,87 @@
/*
* Copyright (c) 1998 HAYAKAWA Koichi. All rights reserved.
* 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.
* 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.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the author.
* 4. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
* 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.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``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 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$
*/
/* $FreeBSD$ */
typedef u_int32_t cardbusreg_t;
typedef int cardbus_intr_line_t;
typedef void *cardbus_chipset_tag_t;
typedef int cardbus_intr_handle_t;
typedef u_int16_t cardbus_vendor_id_t;
typedef u_int16_t cardbus_product_id_t;
#define CARDBUS_ID_REG 0x00
# define CARDBUS_VENDOR_SHIFT 0
# define CARDBUS_VENDOR_MASK 0xffff
# define CARDBUS_VENDOR(id) \
(((id) >> CARDBUS_VENDOR_SHIFT) & CARDBUS_VENDOR_MASK)
# define CARDBUS_PRODUCT_SHIFT 16
# define CARDBUS_PRODUCT_MASK 0xffff
# define CARDBUS_PRODUCT(id) \
(((id) >> CARDBUS_PRODUCT_SHIFT) & CARDBUS_PRODUCT_MASK)
/*
* Register definitions for the Cardbus Bus
*/
#define CARDBUS_COMMAND_STATUS_REG 0x04
/* Cardbus bus constants */
#define CARDBUS_SLOTMAX 0
#define CARDBUS_FUNCMAX 7
# define CARDBUS_COMMAND_IO_ENABLE 0x00000001
# define CARDBUS_COMMAND_MEM_ENABLE 0x00000002
# define CARDBUS_COMMAND_MASTER_ENABLE 0x00000004
/* Cardbus configuration header registers */
#define CARDBUS_BASE0_REG 0x10
#define CARDBUS_BASE1_REG 0x14
#define CARDBUS_BASE2_REG 0x18
#define CARDBUS_BASE3_REG 0x1C
#define CARDBUS_BASE4_REG 0x20
#define CARDBUS_BASE5_REG 0x24
#define CARDBUS_CIS_REG 0x28
# define CARDBUS_CIS_ASIMASK 0x07
# define CARDBUS_CIS_ADDRMASK 0x0ffffff8
# define CARDBUS_CIS_ASI_TUPLE 0x00
# define CARDBUS_CIS_ASI_BAR0 0x01
# define CARDBUS_CIS_ASI_BAR1 0x02
# define CARDBUS_CIS_ASI_BAR2 0x03
# define CARDBUS_CIS_ASI_BAR3 0x04
# define CARDBUS_CIS_ASI_BAR4 0x05
# define CARDBUS_CIS_ASI_BAR5 0x06
# define CARDBUS_CIS_ASI_ROM 0x07
#define CARDBUS_ROM_REG 0x30
/* EXROM offsets for reading CIS */
#define CARDBUS_EXROM_SIGNATURE 0x00
#define CARDBUS_EXROM_DATA_PTR 0x18
#define CARDBUS_CLASS_REG 0x08
#define CARDBUS_EXROM_DATA_SIGNATURE 0x00 /* Signature ("PCIR") */
#define CARDBUS_EXROM_DATA_VENDOR_ID 0x04 /* Vendor Identification */
#define CARDBUS_EXROM_DATA_DEVICE_ID 0x06 /* Device Identification */
#define CARDBUS_EXROM_DATA_LENGTH 0x0a /* PCI Data Structure Length */
#define CARDBUS_EXROM_DATA_REV 0x0c /* PCI Data Structure Revision */
#define CARDBUS_EXROM_DATA_CLASS_CODE 0x0d /* Class Code */
#define CARDBUS_EXROM_DATA_IMAGE_LENGTH 0x10 /* Image Length */
#define CARDBUS_EXROM_DATA_DATA_REV 0x12 /* Revision Level of Code/Data */
#define CARDBUS_EXROM_DATA_CODE_TYPE 0x14 /* Code Type */
#define CARDBUS_EXROM_DATA_INDICATOR 0x15 /* Indicator */
/* BIST, Header Type, Latency Timer, Cache Line Size */
#define CARDBUS_BHLC_REG 0x0c
#define CARDBUS_BIST_SHIFT 24
#define CARDBUS_BIST_MASK 0xff
#define CARDBUS_BIST(bhlcr) \
(((bhlcr) >> CARDBUS_BIST_SHIFT) & CARDBUS_BIST_MASK)
#define CARDBUS_HDRTYPE_SHIFT 16
#define CARDBUS_HDRTYPE_MASK 0xff
#define CARDBUS_HDRTYPE(bhlcr) \
(((bhlcr) >> CARDBUS_HDRTYPE_SHIFT) & CARDBUS_HDRTYPE_MASK)
#define CARDBUS_HDRTYPE_TYPE(bhlcr) \
(CARDBUS_HDRTYPE(bhlcr) & 0x7f)
#define CARDBUS_HDRTYPE_MULTIFN(bhlcr) \
((CARDBUS_HDRTYPE(bhlcr) & 0x80) != 0)
#define CARDBUS_LATTIMER_SHIFT 8
#define CARDBUS_LATTIMER_MASK 0xff
#define CARDBUS_LATTIMER(bhlcr) \
(((bhlcr) >> CARDBUS_LATTIMER_SHIFT) & CARDBUS_LATTIMER_MASK)
#define CARDBUS_CACHELINE_SHIFT 0
#define CARDBUS_CACHELINE_MASK 0xff
#define CARDBUS_CACHELINE(bhlcr) \
(((bhlcr) >> CARDBUS_CACHELINE_SHIFT) & CARDBUS_CACHELINE_MASK)
/* Base Resisters */
#define CARDBUS_BASE0_REG 0x10
#define CARDBUS_BASE1_REG 0x14
#define CARDBUS_BASE2_REG 0x18
#define CARDBUS_BASE3_REG 0x1C
#define CARDBUS_BASE4_REG 0x20
#define CARDBUS_BASE5_REG 0x24
#define CARDBUS_CIS_REG 0x28
# define CARDBUS_CIS_ASIMASK 0x07
# define CARDBUS_CIS_ADDRMASK 0x0ffffff8
#define CARDBUS_INTERRUPT_REG 0x3c
/* useful macros */
#define CARDBUS_CIS_ADDR(x) \
(CARDBUS_CIS_ADDRMASK & (x))
#define CARDBUS_CIS_ASI_BAR(x) \
(((CARDBUS_CIS_ASIMASK & (x))-1)*4+0x10)
#define CARDBUS_CIS_ASI_ROM_IMAGE(x) \
(((x) >> 28) & 0xf)
#define CARDBUS_MAPREG_MEM_ADDR_MASK 0x0ffffff0
#define CARDBUS_MAPREG_MEM_ADDR(mr) \
((mr) & CARDBUS_MAPREG_MEM_ADDR_MASK)
#define CARDBUS_MAPREG_MEM_SIZE(mr) \
(CARDBUS_MAPREG_MEM_ADDR(mr) & -CARDBUS_MAPREG_MEM_ADDR(mr))

View File

@ -1,180 +1,39 @@
/* $Id: cardbusvar.h,v 1.1.2.1 1999/02/16 16:46:08 haya Exp $ */
/*
* Copyright (c) 1998 HAYAKAWA Koichi. All rights reserved.
* 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.
* 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.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the author.
* 4. The name of the author may not be used to endorse or promote products
* derived from this software without specific prior written permission.
* 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.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``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 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$
*/
/* $FreeBSD$ */
#if !defined SYS_DEV_PCCARD_CARDBUSVAR_H
#define SYS_DEV_PCCARD_CARDBUSVAR_H
#include <pci/pcivar.h> /* XXX */
typedef pcitag_t cardbustag_t; /* XXX */
/*
* Structure definitions for the Cardbus Bus driver
*/
typedef struct cardbus_functions {
int (*cardbus_ctrl) __P((cardbus_chipset_tag_t, int));
int (*cardbus_power) __P((cardbus_chipset_tag_t, int));
int (*cardbus_mem_open) __P((cardbus_chipset_tag_t, int, u_int32_t, u_int32_t));
int (*cardbus_mem_close) __P((cardbus_chipset_tag_t, int));
int (*cardbus_io_open) __P((cardbus_chipset_tag_t, int, u_int32_t, u_int32_t));
int (*cardbus_io_close) __P((cardbus_chipset_tag_t, int));
void *(*cardbus_intr_establish) __P((cardbus_chipset_tag_t, int irq, int level, int (*ih)(void *), void *sc));
void (*cardbus_intr_disestablish) __P((cardbus_chipset_tag_t ct, void *ih));
cardbustag_t (*cardbus_make_tag) __P((cardbus_chipset_tag_t, int, int, int));
void (*cardbus_free_tag) __P((cardbus_chipset_tag_t, cardbustag_t));
cardbusreg_t (*cardbus_conf_read) __P((cardbus_chipset_tag_t, cardbustag_t, int));
void (*cardbus_conf_write) __P((cardbus_chipset_tag_t, cardbustag_t, int, cardbusreg_t));
} cardbus_function_t, *cardbus_function_tag_t;
/**********************************************************************
* struct cbslot_attach_args is the attach argument for cardbus slot.
**********************************************************************/
struct cbslot_attach_args {
char *cba_busname;
bus_space_tag_t cba_iot; /* cardbus i/o space tag */
bus_space_tag_t cba_memt; /* cardbus mem space tag */
bus_dma_tag_t cba_dmat; /* DMA tag */
int cba_bus; /* cardbus bus number */
int cba_function; /* slot number on this Host Bus Adaptor */
cardbus_chipset_tag_t cba_cc; /* cardbus chipset */
cardbus_function_tag_t cba_cf; /* cardbus functions */
int cba_intrline; /* interrupt line */
struct cardbus_devinfo {
struct resource_list resources;
pcicfgregs cfg;
struct pci_conf conf;
};
#define cbslotcf_slot cf_loc[0]
#define CBSLOT_UNK_SLOT -1
/**********************************************************************
* struct cardslot_if is the interface for cardslot.
**********************************************************************/
struct cardslot_if {
struct device *(*if_card_attach) __P((struct cardbus_softc*));
};
/**********************************************************************
* struct cardbus_softc is the softc for cardbus card.
**********************************************************************/
struct cardbus_softc {
struct device sc_dev; /* fundamental device structure */
int sc_bus; /* cardbus bus number */
int sc_device; /* cardbus device number */
int sc_intrline; /* CardBus intrline */
bus_space_tag_t sc_iot; /* CardBus I/O space tag */
bus_space_tag_t sc_memt; /* CardBus MEM space tag */
bus_dma_tag_t sc_dmat; /* DMA tag */
cardbus_chipset_tag_t sc_cc; /* CardBus chipset */
cardbus_function_tag_t sc_cf; /* CardBus function */
int sc_volt; /* applied Vcc voltage */
#define PCCARD_33V 0x02
#define PCCARD_XXV 0x04
#define PCCARD_YYV 0x08
struct cardslot_if sc_if;
};
void
cardslot_if_setup __P((struct cardbus_softc*));
/**********************************************************************
* struct cbslot_attach_args is the attach argument for cardbus card.
**********************************************************************/
struct cardbus_attach_args {
int ca_unit;
cardbus_chipset_tag_t ca_cc;
cardbus_function_tag_t ca_cf;
bus_space_tag_t ca_iot; /* CardBus I/O space tag */
bus_space_tag_t ca_memt; /* CardBus MEM space tag */
bus_dma_tag_t ca_dmat; /* DMA tag */
u_int ca_device;
u_int ca_function;
cardbustag_t ca_tag;
cardbusreg_t ca_id;
cardbusreg_t ca_class;
/* interrupt information */
cardbus_intr_line_t ca_intrline;
};
#define CARDBUS_ENABLE 1 /* enable the channel */
#define CARDBUS_DISABLE 2 /* disable the channel */
#define CARDBUS_RESET 4
#define CARDBUS_CD 7
# define CARDBUS_NOCARD 0
# define CARDBUS_5V_CARD 0x01 /* XXX: It must not exist */
# define CARDBUS_3V_CARD 0x02
# define CARDBUS_XV_CARD 0x04
# define CARDBUS_YV_CARD 0x08
#define CARDBUS_IO_ENABLE 100
#define CARDBUS_IO_DISABLE 101
#define CARDBUS_MEM_ENABLE 102
#define CARDBUS_MEM_DISABLE 103
#define CARDBUS_BM_ENABLE 104 /* bus master */
#define CARDBUS_BM_DISABLE 105
#define CARDBUS_VCC_UC 0x0000
#define CARDBUS_VCC_3V 0x0001
#define CARDBUS_VCC_XV 0x0002
#define CARDBUS_VCC_YV 0x0003
#define CARDBUS_VCC_0V 0x0004
#define CARDBUS_VCC_5V 0x0005 /* ??? */
#define CARDBUS_VCCMASK 0x000f
#define CARDBUS_VPP_UC 0x0000
#define CARDBUS_VPP_VCC 0x0010
#define CARDBUS_VPP_12V 0x0030
#define CARDBUS_VPP_0V 0x0040
#define CARDBUS_VPPMASK 0x00f0
/**********************************************************************
* Locators devies that attach to 'cardbus', as specified to config.
**********************************************************************/
#include "locators.h"
#define cardbuscf_dev cf_loc[CARDBUSCF_DEV]
#define CARDBUS_UNK_DEV CARDBUSCF_DEV_DEFAULT
#define cardbuscf_function cf_loc[CARDBUSCF_FUNC]
#define CARDBUS_UNK_FUNCTION CARDBUSCF_FUNC_DEFAULT
struct device *cardbus_attach_card __P((struct cardbus_softc *));
void *cardbus_intr_establish __P((cardbus_chipset_tag_t, cardbus_function_tag_t, cardbus_intr_handle_t irq, int level, int (*func) (void *), void *arg));
void cardbus_intr_disestablish __P((cardbus_chipset_tag_t, cardbus_function_tag_t, void *handler));
#define cardbus_conf_read(cc, cf, tag, offs) ((cf)->cardbus_conf_read)((cc), (tag), (offs))
#define cardbus_conf_write(cc, cf, tag, offs, val) ((cf)->cardbus_conf_write)((cc), (tag), (offs), (val))
#define cardbus_make_tag(cc, cf, bus, device, function) ((cf)->cardbus_make_tag)((cc), (bus), (device), (function))
#define cardbus_free_tag(cc, cf, tag) ((cf)->cardbus_free_tag)((cc), (tag))
#endif /* SYS_DEV_PCCARD_CARDBUSVAR_H */

1713
sys/dev/pccbb/pccbb.c Normal file

File diff suppressed because it is too large Load Diff

69
sys/dev/pccbb/pccbb_if.m Normal file
View File

@ -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
};

188
sys/dev/pccbb/pccbbreg.h Normal file
View File

@ -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

105
sys/dev/pccbb/pccbbvar.h Normal file
View File

@ -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