]> rtime.felk.cvut.cz Git - lincan.git/blobdiff - lincan/src/usbcan.c
Added vendor functions to embedded application, data transferred by usb channel seria...
[lincan.git] / lincan / src / usbcan.c
index aff02d3095df5414ce537d9fe46d3083505b46f5..a18f8621cda002f65ace1943d966577e9c257cef 100644 (file)
@@ -8,14 +8,26 @@
 #include "../include/can.h"
 #include "../include/can_sysdep.h"
 #include "../include/main.h"
+#include "../include/devcommon.h"
+#include "../include/setup.h"
 #include "../include/usbcan.h"
 
-/*
- * IO_RANGE is the io-memory range that gets reserved, please adjust according
- * your hardware. Example: #define IO_RANGE 0x100 for i82527 chips or
- * #define IO_RANGE 0x20 for sja1000 chips in basic CAN mode.
- */
-#define IO_RANGE 0x100
+static int usbcan_probe(struct usb_interface *interface, const struct usb_device_id *id);
+static void usbcan_disconnect(struct usb_interface *interface);
+
+/* table of devices that work with this driver */
+static struct usb_device_id usbcan_table [] = {
+       { USB_DEVICE(USBCAN_VENDOR_ID, USBCAN_PRODUCT_ID) },
+       { }                                     /* Terminating entry */
+};
+MODULE_DEVICE_TABLE(usb, usbcan_table);
+
+static struct usb_driver usbcan_driver = {
+       .name =         "usbcan",
+       .id_table = usbcan_table,
+       .probe =        usbcan_probe,
+       .disconnect =   usbcan_disconnect,
+};
 
 /**
  * usbcan_request_io: - reserve io or memory range for can board
  */
 int usbcan_request_io(struct candevice_t *candev)
 {
-       if (!can_request_io_region(candev->io_addr,IO_RANGE,DEVICE_NAME)) {
-               CANMSG("Unable to open port: 0x%lx\n",candev->io_addr);
-               return -ENODEV;
-       }else {
-               DEBUGMSG("Registered IO-memory: 0x%lx - 0x%lx\n", candev->io_addr, candev->io_addr + IO_RANGE - 1);
-       }
+       struct usbcan_usb *dev = (struct usbcan_usb*)candev->sysdevptr.anydev;
+
+       /* start kernel thread */
+       dev->rcvthread.arg = dev;
+       start_kthread(usbcan_read_kthread, &dev->rcvthread);
+
+       /* Adding link to can device into usbcan_usb struct */
+       ((struct usbcan_usb*)candev->sysdevptr.anydev)->candev=candev;
        return 0;
 }
 
@@ -56,8 +70,14 @@ int usbcan_request_io(struct candevice_t *candev)
  */
 int usbcan_release_io(struct candevice_t *candev)
 {
-       can_release_io_region(candev->io_addr,IO_RANGE);
+       struct usbcan_usb *dev = ((struct usbcan_usb*)candev->sysdevptr.anydev);
 
+       /* terminate the kernel thread */
+       if (dev->rcv){
+               usb_kill_urb(dev->rcv);
+               usb_free_urb(dev->rcv);
+       }
+       stop_kthread(&dev->rcvthread);
        return 0;
 }
 
@@ -76,8 +96,6 @@ int usbcan_reset(struct candevice_t *candev)
        return 0;
 }
 
-#define RESET_ADDR 0x0
-
 /**
  * usbcan_init_hw_data - Initialize hardware cards
  * @candev: Pointer to candevice/board structure
@@ -103,82 +121,6 @@ int usbcan_init_hw_data(struct candevice_t *candev)
        return 0;
 }
 
-/**
- * usbcan_init_chip_data - Initialize chips
- * @candev: Pointer to candevice/board structure
- * @chipnr: Number of the CAN chip on the hardware card
- *
- * The function usbcan_init_chip_data() is used to initialize the hardware
- * structure containing information about the CAN chips.
- * %CHIP_TYPE represents the type of CAN chip. %CHIP_TYPE can be "i82527" or
- * "sja1000".
- * The @chip_base_addr entry represents the start of the 'official' memory map
- * of the installed chip. It's likely that this is the same as the @io_addr
- * argument supplied at module loading time.
- * The @clock entry holds the chip clock value in Hz.
- * The entry @sja_cdr_reg holds hardware specific options for the Clock Divider
- * register. Options defined in the %sja1000.h file:
- * %sjaCDR_CLKOUT_MASK, %sjaCDR_CLK_OFF, %sjaCDR_RXINPEN, %sjaCDR_CBP, %sjaCDR_PELICAN
- * The entry @sja_ocr_reg holds hardware specific options for the Output Control
- * register. Options defined in the %sja1000.h file:
- * %sjaOCR_MODE_BIPHASE, %sjaOCR_MODE_TEST, %sjaOCR_MODE_NORMAL, %sjaOCR_MODE_CLOCK,
- * %sjaOCR_TX0_LH, %sjaOCR_TX1_ZZ.
- * The entry @int_clk_reg holds hardware specific options for the Clock Out
- * register. Options defined in the %i82527.h file:
- * %iCLK_CD0, %iCLK_CD1, %iCLK_CD2, %iCLK_CD3, %iCLK_SL0, %iCLK_SL1.
- * The entry @int_bus_reg holds hardware specific options for the Bus
- * Configuration register. Options defined in the %i82527.h file:
- * %iBUS_DR0, %iBUS_DR1, %iBUS_DT1, %iBUS_POL, %iBUS_CBY.
- * The entry @int_cpu_reg holds hardware specific options for the cpu interface
- * register. Options defined in the %i82527.h file:
- * %iCPU_CEN, %iCPU_MUX, %iCPU_SLP, %iCPU_PWD, %iCPU_DMC, %iCPU_DSC, %iCPU_RST.
- * Return Value: The function always returns zero
- * File: src/usbcan.c
- */
-int usbcan_init_chip_data(struct candevice_t *candev, int chipnr)
-{
-       canchip_t chip=candev->chip[chipnr];
-
-       chip->chip_type="usbcan";
-       chip->max_objects=1;
-       usbcan_register(chip->chipspecops);
-
-       CANMSG("initializing usbcan chip operations\n");
-       chipspecops->chip_config=usbcan_chip_config;
-       chipspecops->baud_rate=usbcan_baud_rate;
-       chipspecops->standard_mask=usbcan_standard_mask;
-       chipspecops->extended_mask=usbcan_extended_mask;
-       chipspecops->message15_mask=usbcan_extended_mask;
-       chipspecops->clear_objects=usbcan_clear_objects;
-       chipspecops->config_irqs=usbcan_config_irqs;
-       chipspecops->pre_read_config=usbcan_pre_read_config;
-       chipspecops->pre_write_config=usbcan_pre_write_config;
-       chipspecops->send_msg=usbcan_send_msg;
-       chipspecops->check_tx_stat=usbcan_check_tx_stat;
-       chipspecops->wakeup_tx=usbcan_wakeup_tx;
-       chipspecops->remote_request=usbcan_remote_request;
-       chipspecops->enable_configuration=usbcan_enable_configuration;
-       chipspecops->disable_configuration=usbcan_disable_configuration;
-       chipspecops->attach_to_chip=usbcan_attach_to_chip;
-       chipspecops->release_chip=usbcan_release_chip;
-       chipspecops->set_btregs=usbcan_set_btregs;
-       chipspecops->start_chip=usbcan_start_chip;
-       chipspecops->stop_chip=usbcan_stop_chip;
-       chipspecops->irq_handler=usbcan_irq_handler;
-       chipspecops->irq_accept=NULL;
-
-       candev->chip[chipnr]->chip_base_addr=candev->io_addr;
-       candev->chip[chipnr]->clock = 16000000;
-       candev->chip[chipnr]->int_cpu_reg = iCPU_DSC;
-       candev->chip[chipnr]->int_clk_reg = iCLK_SL1;
-       candev->chip[chipnr]->int_bus_reg = iBUS_CBY;
-       candev->chip[chipnr]->sja_cdr_reg = sjaCDR_CBP | sjaCDR_CLK_OFF;
-       candev->chip[chipnr]->sja_ocr_reg = sjaOCR_MODE_NORMAL |
-                                                               sjaOCR_TX0_LH;
-
-       return 0;
-}
-
 /**
  * usbcan_init_obj_data - Initialize message buffers
  * @chip: Pointer to chip specific structure
@@ -198,7 +140,7 @@ int usbcan_init_chip_data(struct candevice_t *candev, int chipnr)
  */
 int usbcan_init_obj_data(struct canchip_t *chip, int objnr)
 {
-       chip->msgobj[objnr]->obj_base_addr=chip->chip_base_addr+(objnr+1)*0x10;
+       chip->msgobj[objnr]->obj_base_addr=chip->chip_base_addr+(objnr+1)*0x10;
 
        return 0;
 }
@@ -220,37 +162,6 @@ int usbcan_program_irq(struct candevice_t *candev)
        return 0;
 }
 
-/**
- * usbcan_write_register - Low level write register routine
- * @data: data to be written
- * @address: memory address to write to
- *
- * The function usbcan_write_register() is used to write to hardware registers
- * on the CAN chip. You should only have to edit this function if your hardware
- * uses some specific write process.
- * Return Value: The function does not return a value
- * File: src/usbcan.c
- */
-void usbcan_write_register(unsigned data, unsigned long address)
-{
-       outb(data,address);
-}
-
-/**
- * usbcan_read_register - Low level read register routine
- * @address: memory address to read from
- *
- * The function usbcan_read_register() is used to read from hardware registers
- * on the CAN chip. You should only have to edit this function if your hardware
- * uses some specific read process.
- * Return Value: The function returns the value stored in @address
- * File: src/usbcan.c
- */
-unsigned usbcan_read_register(unsigned long address)
-{
-       return inb(address);
-}
-
 /* !!! Don't change this function !!! */
 int usbcan_register(struct hwspecops_t *hwspecops)
 {
@@ -260,62 +171,20 @@ int usbcan_register(struct hwspecops_t *hwspecops)
        hwspecops->init_hw_data = usbcan_init_hw_data;
        hwspecops->init_chip_data = usbcan_init_chip_data;
        hwspecops->init_obj_data = usbcan_init_obj_data;
-       hwspecops->write_register = usbcan_write_register;
-       hwspecops->read_register = usbcan_read_register;
+       hwspecops->write_register = NULL;
+       hwspecops->read_register = NULL;
        hwspecops->program_irq = usbcan_program_irq;
        return 0;
 }
 
-static const char *sja1000_ecc_errc_str[]={
-       "bit error",
-       "form error",
-       "stuff error",
-       "other type of error"
-};
-
-static const char *sja1000_ecc_seg_str[]={
-       "?0?",
-       "?1?",
-       "ID.28 to ID.21",
-       "start of frame",
-       "bit SRTR",
-       "bit IDE",
-       "ID.20 to ID.18",
-       "ID.17 to ID.13",
-       "CRC sequence",
-       "reserved bit 0",
-       "data field",
-       "data length code",
-       "bit RTR",
-       "reserved bit 1",
-       "ID.4 to ID.0",
-       "ID.12 to ID.5",
-       "?16?"
-       "active error flag",
-       "intermission",
-       "tolerate dominant bits",
-       "?20?",
-       "?21?",
-       "passive error flag",
-       "error delimiter",
-       "CRC delimiter",
-       "acknowledge slot",
-       "end of frame",
-       "acknowledge delimiter",
-       "overload flag",
-       "?29?",
-       "?30?",
-       "?31?"
-};
-
-#endif /*CONFIG_OC_LINCAN_DETAILED_ERRORS*/
-
 static int sja1000_report_error_limit_counter;
 
 static void sja1000_report_error(struct canchip_t *chip,
                                unsigned sr, unsigned ir, unsigned ecc)
 {
-       if(sja1000_report_error_limit_counter>=100)
+       /*TODO : Error reporting from device */
+
+/*     if(sja1000_report_error_limit_counter>=100)
                return;
 
        CANMSG("Error: status register: 0x%x irq_register: 0x%02x error: 0x%02x\n",
@@ -357,27 +226,6 @@ static void sja1000_report_error(struct canchip_t *chip,
  */
 int usbcan_enable_configuration(struct canchip_t *chip)
 {
-       int i=0;
-       enum sja1000_PeliCAN_MOD flags;
-
-       can_disable_irq(chip->chip_irq);
-
-       flags=can_read_reg(chip,SJAMOD);
-
-       while ((!(flags & sjaMOD_RM)) && (i<=10)) {
-               can_write_reg(chip, sjaMOD_RM, SJAMOD);
-// TODO: configurable sjaMOD_AFM (32/16 bit acceptance filter)
-// config sjaMOD_LOM (listen only)
-               udelay(100);
-               i++;
-               flags=can_read_reg(chip, SJAMOD);
-       }
-       if (i>=10) {
-               CANMSG("Reset error\n");
-               can_enable_irq(chip->chip_irq);
-               return -ENODEV;
-       }
-
        return 0;
 }
 
@@ -387,27 +235,6 @@ int usbcan_enable_configuration(struct canchip_t *chip)
  */
 int usbcan_disable_configuration(struct canchip_t *chip)
 {
-       int i=0;
-       enum sja1000_PeliCAN_MOD flags;
-
-       flags=can_read_reg(chip,SJAMOD);
-
-       while ( (flags & sjaMOD_RM) && (i<=50) ) {
-// could be as long as 11*128 bit times after buss-off
-               can_write_reg(chip, 0, SJAMOD);
-// TODO: configurable sjaMOD_AFM (32/16 bit acceptance filter)
-// config sjaMOD_LOM (listen only)
-               udelay(100);
-               i++;
-               flags=can_read_reg(chip, SJAMOD);
-       }
-       if (i>=10) {
-               CANMSG("Error leaving reset status\n");
-               return -ENODEV;
-       }
-
-       can_enable_irq(chip->chip_irq);
-
        return 0;
 }
 
@@ -425,48 +252,6 @@ int usbcan_disable_configuration(struct canchip_t *chip)
  */
 int usbcan_chip_config(struct canchip_t *chip)
 {
-       int i;
-       unsigned char n, r;
-
-       if (usbcan_enable_configuration(chip))
-               return -ENODEV;
-
-       /* Set mode, clock out, comparator */
-       can_write_reg(chip,sjaCDR_PELICAN|chip->sja_cdr_reg,SJACDR);
-
-       /* Ensure, that interrupts are disabled even on the chip level now */
-       can_write_reg(chip, sjaDISABLE_INTERRUPTS, SJAIER);
-
-       /* Set driver output configuration */
-       can_write_reg(chip,chip->sja_ocr_reg,SJAOCR);
-
-       /* Simple check for chip presence */
-       for (i=0, n=0x5a; i<8; i++, n+=0xf) {
-               can_write_reg(chip,n,SJAACR0+i);
-       }
-       for (i=0, n=0x5a; i<8; i++, n+=0xf) {
-               r = n^can_read_reg(chip,SJAACR0+i);
-               if (r) {
-                       CANMSG("usbcan_chip_config: chip connection broken,"
-                               " readback differ 0x%02x\n", r);
-                       return -ENODEV;
-               }
-       }
-
-
-       if (usbcan_extended_mask(chip,0x00000000, 0xffffffff))
-               return -ENODEV;
-
-       if (!chip->baudrate)
-               chip->baudrate=1000000;
-       if (usbcan_baud_rate(chip,chip->baudrate,chip->clock,0,75,0))
-               return -ENODEV;
-
-       /* Enable hardware interrupts */
-       can_write_reg(chip, sjaENABLE_INTERRUPTS, SJAIER);
-
-       usbcan_disable_configuration(chip);
-
        return 0;
 }
 
@@ -481,25 +266,42 @@ int usbcan_chip_config(struct canchip_t *chip)
  */
 int usbcan_extended_mask(struct canchip_t *chip, unsigned long code, unsigned  long mask)
 {
-       int i;
-
-       if (usbcan_enable_configuration(chip))
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+
+       __u8 usbbuf[16];
+
+       *(uint32_t *)(usbbuf)=cpu_to_le32(mask);
+       *(uint32_t *)(usbbuf+4)=cpu_to_le32(code);
+
+       retval=usb_control_msg(dev->udev,
+               usb_sndctrlpipe(dev->udev, dev->ctl_out_endpointAddr),
+               USBCAN_VENDOR_EXT_MASK_SET,
+               USB_TYPE_VENDOR,
+               0, chip->chip_idx,
+               &usbbuf, 16,
+               10000);
+       if (retval<0)
                return -ENODEV;
 
-// LSB to +3, MSB to +0
-       for(i=SJA_PeliCAN_AC_LEN; --i>=0;) {
-               can_write_reg(chip,code&0xff,SJAACR0+i);
-               can_write_reg(chip,mask&0xff,SJAAMR0+i);
-               code >>= 8;
-               mask >>= 8;
+       retval = usb_control_msg(dev->udev,
+               usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+               USBCAN_VENDOR_EXT_MASK_STATUS,
+               USB_TYPE_VENDOR,
+               0, chip->chip_idx,
+               &usbbuf, 16,
+               10000);
+
+       if (retval==16){
+               if(usbbuf[0]==1){
+                       DEBUGMSG("Setting acceptance code to 0x%lx\n",(unsigned long)code);
+                       DEBUGMSG("Setting acceptance mask to 0x%lx\n",(unsigned long)mask);
+                       return 0;
+               }
        }
 
-       DEBUGMSG("Setting acceptance code to 0x%lx\n",(unsigned long)code);
-       DEBUGMSG("Setting acceptance mask to 0x%lx\n",(unsigned long)mask);
-
-       usbcan_disable_configuration(chip);
-
-       return 0;
+       CANMSG("Setting extended mask failed\n");
+       return -EINVAL;
 }
 
 /**
@@ -517,105 +319,42 @@ int usbcan_extended_mask(struct canchip_t *chip, unsigned long code, unsigned  l
 int usbcan_baud_rate(struct canchip_t *chip, int rate, int clock, int sjw,
                                                        int sampl_pt, int flags)
 {
-       int best_error = 1000000000, error;
-       int best_tseg=0, best_brp=0, best_rate=0, brp=0;
-       int tseg=0, tseg1=0, tseg2=0;
-
-       if (usbcan_enable_configuration(chip))
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+
+       __u8 usbbuf[16];
+
+       *(int32_t *)(usbbuf)=cpu_to_le32(rate);
+       *(int32_t *)(usbbuf+4)=cpu_to_le32(sjw);
+       *(int32_t *)(usbbuf+8)=cpu_to_le32(sampl_pt);
+       *(int32_t *)(usbbuf+12)=cpu_to_le32(flags);
+
+       retval=usb_control_msg(dev->udev,
+               usb_sndctrlpipe(dev->udev, dev->ctl_out_endpointAddr),
+               USBCAN_VENDOR_BAUD_RATE_SET,
+               USB_TYPE_VENDOR,
+               0, chip->chip_idx,
+               &usbbuf, 16,
+               10000);
+       if (retval<0)
                return -ENODEV;
 
-       clock /=2;
-
-       /* tseg even = round down, odd = round up */
-       for (tseg=(0+0+2)*2; tseg<=(sjaMAX_TSEG2+sjaMAX_TSEG1+2)*2+1; tseg++) {
-               brp = clock/((1+tseg/2)*rate)+tseg%2;
-               if (brp == 0 || brp > 64)
-                       continue;
-               error = rate - clock/(brp*(1+tseg/2));
-               if (error < 0)
-                       error = -error;
-               if (error <= best_error) {
-                       best_error = error;
-                       best_tseg = tseg/2;
-                       best_brp = brp-1;
-                       best_rate = clock/(brp*(1+tseg/2));
-               }
+       retval = usb_control_msg(dev->udev,
+               usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+               USBCAN_VENDOR_BAUD_RATE_STATUS,
+               USB_TYPE_VENDOR,
+               0, chip->chip_idx,
+               usbbuf, 16,
+               10000);
+
+       if (retval==16){
+               if(usbbuf[0]==1)
+                       return 0;
        }
-       if (best_error && (rate/best_error < 10)) {
-               CANMSG("baud rate %d is not possible with %d Hz clock\n",
-                                                               rate, 2*clock);
-               CANMSG("%d bps. brp=%d, best_tseg=%d, tseg1=%d, tseg2=%d\n",
-                               best_rate, best_brp, best_tseg, tseg1, tseg2);
-               return -EINVAL;
-       }
-       tseg2 = best_tseg-(sampl_pt*(best_tseg+1))/100;
-       if (tseg2 < 0)
-               tseg2 = 0;
-       if (tseg2 > sjaMAX_TSEG2)
-               tseg2 = sjaMAX_TSEG2;
-       tseg1 = best_tseg-tseg2-2;
-       if (tseg1>sjaMAX_TSEG1) {
-               tseg1 = sjaMAX_TSEG1;
-               tseg2 = best_tseg-tseg1-2;
-       }
-
-       DEBUGMSG("Setting %d bps.\n", best_rate);
-       DEBUGMSG("brp=%d, best_tseg=%d, tseg1=%d, tseg2=%d, sampl_pt=%d\n",
-                                       best_brp, best_tseg, tseg1, tseg2,
-                                       (100*(best_tseg-tseg2)/(best_tseg+1)));
-
-
-       can_write_reg(chip, sjw<<6 | best_brp, SJABTR0);
-       can_write_reg(chip, ((flags & BTR1_SAM) != 0)<<7 | (tseg2<<4)
-                                       | tseg1, SJABTR1);
-
-       usbcan_disable_configuration(chip);
-
-       return 0;
-}
-
-/**
- * usbcan_read: - reads and distributes one or more received messages
- * @chip: pointer to chip state structure
- * @obj: pinter to CAN message queue information
- *
- * File: src/usbcan.c
- */
-void usbcan_read(struct canchip_t *chip, struct msgobj_t *obj) {
-       int i, flags, len, datastart;
-       do {
-               flags = can_read_reg(chip,SJAFRM);
-               if(flags&sjaFRM_FF) {
-                       obj->rx_msg.id =
-                               (can_read_reg(chip,SJAID0)<<21) +
-                               (can_read_reg(chip,SJAID1)<<13) +
-                               (can_read_reg(chip,SJAID2)<<5) +
-                               (can_read_reg(chip,SJAID3)>>3);
-                       datastart = SJADATE;
-               } else {
-                       obj->rx_msg.id =
-                               (can_read_reg(chip,SJAID0)<<3) +
-                               (can_read_reg(chip,SJAID1)>>5);
-                       datastart = SJADATS;
-               }
-               obj->rx_msg.flags =
-                       ((flags & sjaFRM_RTR) ? MSG_RTR : 0) |
-                       ((flags & sjaFRM_FF) ? MSG_EXT : 0);
-               len = flags & sjaFRM_DLC_M;
-               obj->rx_msg.length = len;
-               if(len > CAN_MSG_LENGTH) len = CAN_MSG_LENGTH;
-               for(i=0; i< len; i++) {
-                       obj->rx_msg.data[i]=can_read_reg(chip,datastart+i);
-               }
-
-               /* fill CAN message timestamp */
-               can_filltimestamp(&obj->rx_msg.timestamp);
-
-               canque_filter_msg2edges(obj->qends, &obj->rx_msg);
 
-               can_write_reg(chip, sjaCMR_RRB, SJACMR);
-
-       } while (can_read_reg(chip, SJASR) & sjaSR_RBS);
+       CANMSG("baud rate %d is not possible to set\n",
+               rate);
+       return -EINVAL;
 }
 
 /**
@@ -629,27 +368,7 @@ void usbcan_read(struct canchip_t *chip, struct msgobj_t *obj) {
  */
 int usbcan_pre_read_config(struct canchip_t *chip, struct msgobj_t *obj)
 {
-       int status;
-       status=can_read_reg(chip,SJASR);
-
-       if(status  & sjaSR_BS) {
-               /* Try to recover from error condition */
-               DEBUGMSG("usbcan_pre_read_config bus-off recover 0x%x\n",status);
-               usbcan_enable_configuration(chip);
-               can_write_reg(chip, 0, SJARXERR);
-               can_write_reg(chip, 0, SJATXERR1);
-               can_read_reg(chip, SJAECC);
-               usbcan_disable_configuration(chip);
-       }
-
-       if (!(status&sjaSR_RBS)) {
-               return 0;
-       }
-
-       can_write_reg(chip, sjaDISABLE_INTERRUPTS, SJAIER); //disable interrupts for a moment
-       usbcan_read(chip, obj);
-       can_write_reg(chip, sjaENABLE_INTERRUPTS, SJAIER); //enable interrupts
-       return 1;
+       return 0;
 }
 
 #define MAX_TRANSMIT_WAIT_LOOPS 10
@@ -669,67 +388,35 @@ int usbcan_pre_read_config(struct canchip_t *chip, struct msgobj_t *obj)
 int usbcan_pre_write_config(struct canchip_t *chip, struct msgobj_t *obj,
                                                        struct canmsg_t *msg)
 {
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
        int i=0;
-       unsigned int id;
-       int status;
        int len;
+       __u8 *ptr;
 
        /* Wait until Transmit Buffer Status is released */
-       while ( !((status=can_read_reg(chip, SJASR)) & sjaSR_TBS) &&
+       while ( usbcan_chip_queue_status(chip) &&
                                                i++<MAX_TRANSMIT_WAIT_LOOPS) {
                udelay(i);
        }
-
-       if(status & sjaSR_BS) {
-               /* Try to recover from error condition */
-               DEBUGMSG("usbcan_pre_write_config bus-off recover 0x%x\n",status);
-               usbcan_enable_configuration(chip);
-               can_write_reg(chip, 0, SJARXERR);
-               can_write_reg(chip, 0, SJATXERR1);
-               can_read_reg(chip, SJAECC);
-               usbcan_disable_configuration(chip);
-       }
-       if (!(can_read_reg(chip, SJASR) & sjaSR_TBS)) {
-               CANMSG("Transmit timed out, cancelling\n");
-// here we should check if there is no write/select waiting for this
-// transmit. If so, set error ret and wake up.
-// CHECKME: if we do not disable sjaIER_TIE (TX IRQ) here we get interrupt
-// immediately
-               can_write_reg(chip, sjaCMR_AT, SJACMR);
-               i=0;
-               while ( !(can_read_reg(chip, SJASR) & sjaSR_TBS) &&
-                                               i++<MAX_TRANSMIT_WAIT_LOOPS) {
-                       udelay(i);
-               }
-               if (!(can_read_reg(chip, SJASR) & sjaSR_TBS)) {
-                       CANMSG("Could not cancel, please reset\n");
-                       return -EIO;
-               }
+       if (usbcan_chip_queue_status(chip)){
+               CANMSG("Buffer full, cannot send message\n");
+               return -EIO;
        }
+
+       *(uint8_t *)(dev->tx_msg)=chip->chip_idx & 0xFF;
+
        len = msg->length;
        if(len > CAN_MSG_LENGTH) len = CAN_MSG_LENGTH;
-       /* len &= sjaFRM_DLC_M; ensured by above condition already */
-       can_write_reg(chip, ((msg->flags&MSG_EXT)?sjaFRM_FF:0) |
-               ((msg->flags & MSG_RTR) ? sjaFRM_RTR : 0) | len, SJAFRM);
-       if(msg->flags&MSG_EXT) {
-               id=msg->id<<3;
-               can_write_reg(chip, id & 0xff, SJAID3);
-               id >>= 8;
-               can_write_reg(chip, id & 0xff, SJAID2);
-               id >>= 8;
-               can_write_reg(chip, id & 0xff, SJAID1);
-               id >>= 8;
-               can_write_reg(chip, id, SJAID0);
-               for(i=0; i < len; i++) {
-                       can_write_reg(chip, msg->data[i], SJADATE+i);
-               }
-       } else {
-               id=msg->id<<5;
-               can_write_reg(chip, (id >> 8) & 0xff, SJAID0);
-               can_write_reg(chip, id & 0xff, SJAID1);
-               for(i=0; i < len; i++) {
-                       can_write_reg(chip, msg->data[i], SJADATS+i);
-               }
+
+       *(uint8_t *)(dev->tx_msg+1)=len & 0xFF;
+       *(uint16_t *)(dev->tx_msg+2)=cpu_to_le16(msg->flags);
+       *(uint32_t *)(dev->tx_msg+4)=cpu_to_le32(msg->id);
+
+       for(ptr=dev->tx_msg+8,i=0; i < len; ptr++,i++) {
+               *ptr=msg->data[i] & 0xFF;
+       }
+       for(; i < 8; ptr++,i++) {
+               *ptr=0;
        }
        return 0;
 }
@@ -748,7 +435,23 @@ int usbcan_pre_write_config(struct canchip_t *chip, struct msgobj_t *obj,
 int usbcan_send_msg(struct canchip_t *chip, struct msgobj_t *obj,
                                                        struct canmsg_t *msg)
 {
-       can_write_reg(chip, sjaCMR_TR, SJACMR);
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+       int len,retval;
+
+       set_bit(USBCAN_TX_PENDING,&dev->flags);
+       retval=usb_bulk_msg(dev->udev,
+                       usb_sndbulkpipe(dev->udev, dev->bulk_out_endpointAddr),
+                       &dev->tx_msg, 16,
+                       &len,10000);
+       clear_bit(USBCAN_TX_PENDING,&dev->flags);
+       if (retval){
+               CANMSG("URB error %d\n",retval);
+               return -EIO;
+       }
+       if (len!=sizeof(struct usbcan_canmsg_t)){
+               CANMSG("CAN message not sent\n");
+               return -EIO;
+       }
 
        return 0;
 }
@@ -764,10 +467,9 @@ int usbcan_send_msg(struct canchip_t *chip, struct msgobj_t *obj,
  */
 int usbcan_check_tx_stat(struct canchip_t *chip)
 {
-       if (can_read_reg(chip,SJASR) & sjaSR_TCS)
-               return 0;
-       else
+       if (test_bit(USBCAN_TX_PENDING,&((struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev)->flags))
                return 1;
+       return 0;
 }
 
 /**
@@ -782,15 +484,23 @@ int usbcan_check_tx_stat(struct canchip_t *chip)
 int usbcan_set_btregs(struct canchip_t *chip, unsigned short btr0,
                                                        unsigned short btr1)
 {
-       if (usbcan_enable_configuration(chip))
-               return -ENODEV;
-
-       can_write_reg(chip, btr0, SJABTR0);
-       can_write_reg(chip, btr1, SJABTR1);
-
-       usbcan_disable_configuration(chip);
-
-       return 0;
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+       uint16_t value=(btr1&0xFF)<<8 | (btr0&0xFF);
+
+       retval = usb_control_msg(dev->udev,
+       usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+       USBCAN_VENDOR_SET_BTREGS,
+       USB_TYPE_VENDOR,
+       cpu_to_le16(value), chip->chip_idx,
+       dev->ctl_in_buffer, dev->ctl_in_size,
+       10000);
+
+       if (retval==1){
+               if(dev->ctl_in_buffer[0]==1)
+                       return 0;
+       }
+       return -ENODEV;
 }
 
 /**
@@ -802,14 +512,53 @@ int usbcan_set_btregs(struct canchip_t *chip, unsigned short btr0,
  */
 int usbcan_start_chip(struct canchip_t *chip)
 {
-       enum sja1000_PeliCAN_MOD flags;
-
-       flags = can_read_reg(chip, SJAMOD) & (sjaMOD_LOM|sjaMOD_STM|sjaMOD_AFM|sjaMOD_SM);
-       can_write_reg(chip, flags, SJAMOD);
-
-       sja1000_report_error_limit_counter=0;
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+
+       retval = usb_control_msg(dev->udev,
+       usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+       USBCAN_VENDOR_START_CHIP,
+       USB_TYPE_VENDOR,
+       0, chip->chip_idx,
+       dev->ctl_in_buffer, dev->ctl_in_size,
+       10000);
+
+       if (retval==1){
+               if(dev->ctl_in_buffer[0]==1)
+                       return 0;
+       }
+       return -ENODEV;
+}
 
-       return 0;
+/**
+ * usbcan_chip_queue_status: -  gets queue status from usb device
+ * @chip: pointer to chip state structure
+ *
+ * Return Value: negative value reports error.
+ * 0 means queue is not full
+ * 1 means queue is full
+ * File: src/usbcan.c
+ */
+int usbcan_chip_queue_status(struct canchip_t *chip)
+{
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+
+       retval = usb_control_msg(dev->udev,
+       usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+       USBCAN_VENDOR_CHECK_TX_STAT,
+       USB_TYPE_VENDOR,
+       0, chip->chip_idx,
+       dev->ctl_in_buffer, dev->ctl_in_size,
+       10000);
+
+       if (retval==1){
+               if(dev->ctl_in_buffer[0]==1)
+                       return 0;
+               if(dev->ctl_in_buffer[0]==0)
+                       return 1;
+       }
+       return -ENODEV;
 }
 
 /**
@@ -821,12 +570,22 @@ int usbcan_start_chip(struct canchip_t *chip)
  */
 int usbcan_stop_chip(struct canchip_t *chip)
 {
-       enum sja1000_PeliCAN_MOD flags;
-
-       flags = can_read_reg(chip, SJAMOD) & (sjaMOD_LOM|sjaMOD_STM|sjaMOD_AFM|sjaMOD_SM);
-       can_write_reg(chip, flags|sjaMOD_RM, SJAMOD);
-
-       return 0;
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb*)chip->hostdevice->sysdevptr.anydev;
+
+       retval = usb_control_msg(dev->udev,
+       usb_rcvctrlpipe(dev->udev, dev->ctl_in_endpointAddr),
+       USBCAN_VENDOR_STOP_CHIP,
+       USB_TYPE_VENDOR,
+       0, chip->chip_idx,
+       dev->ctl_in_buffer, dev->ctl_in_size,
+       10000);
+
+       if (retval==1){
+               if(dev->ctl_in_buffer[0]==1)
+                       return 0;
+       }
+       return -ENODEV;
 }
 
 /**
@@ -851,8 +610,6 @@ int usbcan_attach_to_chip(struct canchip_t *chip)
 int usbcan_release_chip(struct canchip_t *chip)
 {
        usbcan_stop_chip(chip);
-       can_write_reg(chip, sjaDISABLE_INTERRUPTS, SJAIER);
-
        return 0;
 }
 
@@ -929,15 +686,15 @@ void usbcan_irq_write_handler(struct canchip_t *chip, struct msgobj_t *obj)
        int cmd;
 
        if(obj->tx_slot){
-               /* Do local transmitted message distribution if enabled */
+               // Do local transmitted message distribution if enabled
                if (processlocal){
-                       /* fill CAN message timestamp */
+                       // fill CAN message timestamp
                        can_filltimestamp(&obj->tx_slot->msg.timestamp);
 
                        obj->tx_slot->msg.flags |= MSG_LOCAL;
                        canque_filter_msg2edges(obj->qends, &obj->tx_slot->msg);
                }
-               /* Free transmitted slot */
+               // Free transmitted slot
                canque_free_outslot(obj->qends, obj->tx_qedge, obj->tx_slot);
                obj->tx_slot=NULL;
        }
@@ -962,7 +719,6 @@ void usbcan_irq_write_handler(struct canchip_t *chip, struct msgobj_t *obj)
                obj->tx_slot=NULL;
                return;
        }
-
 }
 
 #define MAX_RETR 10
@@ -981,7 +737,7 @@ void usbcan_irq_write_handler(struct canchip_t *chip, struct msgobj_t *obj)
  */
 int usbcan_irq_handler(int irq, struct canchip_t *chip)
 {
-       int irq_register, status, error_code;
+/*     int irq_register, status, error_code;
        struct msgobj_t *obj=chip->msgobj[0];
        int loop_cnt=CHIP_MAX_IRQLOOP;
 
@@ -1007,16 +763,8 @@ int usbcan_irq_handler(int irq, struct canchip_t *chip)
                        return CANCHIP_IRQ_STUCK;
                }
 
-               /* (irq_register & sjaIR_RI) */
-               /*      old variant using SJAIR, collides with intended use with irq_accept */
-               if (status & sjaSR_RBS) {
-                       DEBUGMSG("sja1000_irq_handler: RI or RBS\n");
-                       usbcan_read(chip,obj);
-                       obj->ret = 0;
-               }
-
-               /* (irq_register & sjaIR_TI) */
-               /*      old variant using SJAIR, collides with intended use with irq_accept */
+               // (irq_register & sjaIR_TI)
+               //      old variant using SJAIR, collides with intended use with irq_accept
                if (((status & sjaSR_TBS) && can_msgobj_test_fl(obj,TX_PENDING))||
                    (can_msgobj_test_fl(obj,TX_REQUEST))) {
                        DEBUGMSG("sja1000_irq_handler: TI or TX_PENDING and TBS\n");
@@ -1043,7 +791,7 @@ int usbcan_irq_handler(int irq, struct canchip_t *chip)
 
                        if(error_code == 0xd9) {
                                obj->ret= -ENXIO;
-                               /* no such device or address - no ACK received */
+                               // no such device or address - no ACK received
                        }
                        if(obj->tx_retry_cnt++>MAX_RETR) {
                                can_write_reg(chip, sjaCMR_AT, SJACMR); // cancel any transmition
@@ -1056,8 +804,8 @@ int usbcan_irq_handler(int irq, struct canchip_t *chip)
 
                        if(obj->tx_slot){
                                canque_notify_inends(obj->tx_qedge, CANQUEUE_NOTIFY_ERRTX_BUS);
-                               /*canque_free_outslot(obj->qends, obj->tx_qedge, obj->tx_slot);
-                               obj->tx_slot=NULL;*/
+                               //canque_free_outslot(obj->qends, obj->tx_qedge, obj->tx_slot);
+                               //obj->tx_slot=NULL;
                        }
 
                } else {
@@ -1077,7 +825,7 @@ int usbcan_irq_handler(int irq, struct canchip_t *chip)
        } while((irq_register & (sjaIR_BEI|sjaIR_EPI|sjaIR_DOI|sjaIR_EI|sjaIR_RI)) ||
                (can_msgobj_test_fl(obj,TX_REQUEST) && !can_msgobj_test_fl(obj,TX_LOCK)) ||
                (status & sjaSR_RBS));
-
+*/
        return CANCHIP_IRQ_HANDLED;
 }
 
@@ -1102,7 +850,7 @@ int usbcan_wakeup_tx(struct canchip_t *chip, struct msgobj_t *obj)
        while(!can_msgobj_test_and_set_fl(obj,TX_LOCK)){
                can_msgobj_clear_fl(obj,TX_REQUEST);
 
-               if (can_read_reg(chip, SJASR) & sjaSR_TBS){
+               if (!usbcan_chip_queue_status(chip)){
                        obj->tx_retry_cnt=0;
                        usbcan_irq_write_handler(chip, obj);
                }
@@ -1116,8 +864,31 @@ int usbcan_wakeup_tx(struct canchip_t *chip, struct msgobj_t *obj)
        return 0;
 }
 
-int usbcan_register(struct chipspecops_t *chipspecops)
+int usbcan_chipregister(struct chipspecops_t *chipspecops)
 {
+       CANMSG("initializing usbcan chip operations\n");
+       chipspecops->chip_config=usbcan_chip_config;
+       chipspecops->baud_rate=usbcan_baud_rate;
+       chipspecops->standard_mask=usbcan_standard_mask;
+       chipspecops->extended_mask=usbcan_extended_mask;
+       chipspecops->message15_mask=usbcan_extended_mask;
+       chipspecops->clear_objects=usbcan_clear_objects;
+       chipspecops->config_irqs=usbcan_config_irqs;
+       chipspecops->pre_read_config=usbcan_pre_read_config;
+       chipspecops->pre_write_config=usbcan_pre_write_config;
+       chipspecops->send_msg=usbcan_send_msg;
+       chipspecops->check_tx_stat=usbcan_check_tx_stat;
+       chipspecops->wakeup_tx=usbcan_wakeup_tx;
+       chipspecops->remote_request=usbcan_remote_request;
+       chipspecops->enable_configuration=usbcan_enable_configuration;
+       chipspecops->disable_configuration=usbcan_disable_configuration;
+       chipspecops->attach_to_chip=usbcan_attach_to_chip;
+       chipspecops->release_chip=usbcan_release_chip;
+       chipspecops->set_btregs=usbcan_set_btregs;
+       chipspecops->start_chip=usbcan_start_chip;
+       chipspecops->stop_chip=usbcan_stop_chip;
+       chipspecops->irq_handler=usbcan_irq_handler;
+       chipspecops->irq_accept=NULL;
        return 0;
 }
 
@@ -1131,5 +902,319 @@ int usbcan_register(struct chipspecops_t *chipspecops)
  */
 int usbcan_fill_chipspecops(struct canchip_t *chip)
 {
+       chip->chip_type="usbcan";
+       chip->max_objects=1;
+       usbcan_chipregister(chip->chipspecops);
+       return 0;
+}
+
+/**
+ * usbcan_init_chip_data - Initialize chips
+ * @candev: Pointer to candevice/board structure
+ * @chipnr: Number of the CAN chip on the hardware card
+ *
+ * The function usbcan_init_chip_data() is used to initialize the hardware
+ * structure containing information about the CAN chips.
+ * %CHIP_TYPE represents the type of CAN chip. %CHIP_TYPE can be "i82527" or
+ * "sja1000".
+ * The @chip_base_addr entry represents the start of the 'official' memory map
+ * of the installed chip. It's likely that this is the same as the @io_addr
+ * argument supplied at module loading time.
+ * The @clock entry holds the chip clock value in Hz.
+ * The entry @sja_cdr_reg holds hardware specific options for the Clock Divider
+ * register. Options defined in the %sja1000.h file:
+ * %sjaCDR_CLKOUT_MASK, %sjaCDR_CLK_OFF, %sjaCDR_RXINPEN, %sjaCDR_CBP, %sjaCDR_PELICAN
+ * The entry @sja_ocr_reg holds hardware specific options for the Output Control
+ * register. Options defined in the %sja1000.h file:
+ * %sjaOCR_MODE_BIPHASE, %sjaOCR_MODE_TEST, %sjaOCR_MODE_NORMAL, %sjaOCR_MODE_CLOCK,
+ * %sjaOCR_TX0_LH, %sjaOCR_TX1_ZZ.
+ * The entry @int_clk_reg holds hardware specific options for the Clock Out
+ * register. Options defined in the %i82527.h file:
+ * %iCLK_CD0, %iCLK_CD1, %iCLK_CD2, %iCLK_CD3, %iCLK_SL0, %iCLK_SL1.
+ * The entry @int_bus_reg holds hardware specific options for the Bus
+ * Configuration register. Options defined in the %i82527.h file:
+ * %iBUS_DR0, %iBUS_DR1, %iBUS_DT1, %iBUS_POL, %iBUS_CBY.
+ * The entry @int_cpu_reg holds hardware specific options for the cpu interface
+ * register. Options defined in the %i82527.h file:
+ * %iCPU_CEN, %iCPU_MUX, %iCPU_SLP, %iCPU_PWD, %iCPU_DMC, %iCPU_DSC, %iCPU_RST.
+ * Return Value: The function always returns zero
+ * File: src/usbcan.c
+ */
+int usbcan_init_chip_data(struct candevice_t *candev, int chipnr)
+{
+       struct canchip_t *chip=candev->chip[chipnr];
+
+       usbcan_fill_chipspecops(chip);
+
+       candev->chip[chipnr]->flags|=CHIP_IRQ_CUSTOM;
+       candev->chip[chipnr]->chip_base_addr=0;
+       candev->chip[chipnr]->clock = 0;
+
        return 0;
 }
+
+
+
+/* --------------------------------------------------------------------------------------------------- */
+
+static void usbcan_rcv(struct urb *urb)
+{
+       struct usbcan_usb *dev = urb->context;
+       int retval;
+
+       switch (urb->status) {
+       case 0:
+               /* success */
+               set_bit(USBCAN_DATA_READ,&dev->flags);
+               wake_up(&dev->rcvthread.queue);
+               return;
+       case -ECONNRESET:
+       case -ENOENT:
+       case -ESHUTDOWN:
+               /* this urb is terminated, clean up */
+               CANMSG("%s - urb shutting down with status: %d\n", __FUNCTION__, urb->status);
+               set_bit(USBCAN_TERMINATE,&dev->flags);
+               wake_up(&dev->rcvthread.queue);
+               return;
+       default:
+               CANMSG("%s - nonzero urb status received: %d\n", __FUNCTION__, urb->status);
+               break;
+       }
+
+       retval = usb_submit_urb (urb, GFP_ATOMIC);
+       if (retval<0){
+               CANMSG("%s - usb_submit_urb failed with result %d\n",
+                    __FUNCTION__, retval);
+               set_bit(USBCAN_ERROR,&dev->flags);
+               wake_up(&dev->rcvthread.queue);
+       }
+}
+
+void usbcan_read_kthread(kthread_t *kthread)
+{
+       int retval;
+       struct usbcan_usb *dev=(struct usbcan_usb *)kthread->arg;
+       struct msgobj_t *obj;
+
+  /* setup the thread environment */
+  init_kthread(kthread, "usbcan");
+
+  /* this is normal work to do */
+  CANMSG ("usbcan thread started!\n");
+
+       dev->rcv = usb_alloc_urb(0, GFP_KERNEL);
+       if (!dev->rcv){
+               CANMSG("Error allocating usb urb\n");
+               goto error;
+       }
+       dev->rcv->dev = dev->udev;
+       usb_fill_bulk_urb(dev->rcv, dev->udev,
+                        usb_rcvbulkpipe(dev->udev, dev->bulk_in_endpointAddr),
+                        &dev->rcv_msg, 16,
+                        usbcan_rcv, dev);
+
+  /* an endless loop in which we are doing our work */
+  for(;;)
+  {
+               retval=usb_submit_urb(dev->rcv, GFP_KERNEL);
+               if (retval){
+                       CANMSG("URB error %d\n",retval);
+                       break;
+               }
+               /* fall asleep */
+               wait_event_interruptible(kthread->queue,
+                       test_bit(USBCAN_DATA_READ,&dev->flags)
+                       || test_bit(USBCAN_TERMINATE,&dev->flags)
+                       || test_bit(USBCAN_ERROR,&dev->flags)
+               );
+
+               /* We need to do a memory barrier here to be sure that
+               the flags are visible on all CPUs. */
+               mb();
+
+               /* here we are back from sleep because we caught a signal. */
+               if (kthread->terminate)
+               {
+                       /* we received a request to terminate ourself */
+                       break;
+               }
+
+               if (test_bit(USBCAN_ERROR,&dev->flags)){
+                       CANMSG("URB error %d\n",retval);
+                       break;
+               }
+
+               { /* Normal work to do */
+                       if (test_bit(USBCAN_DATA_READ,&dev->flags)){
+                               int i, len;
+                               clear_bit(USBCAN_DATA_READ,&dev->flags);
+
+                               if ((dev->candev->chip[dev->rcv_msg[0]])&&
+                                       (dev->candev->chip[dev->rcv_msg[0]]->flags & CHIP_CONFIGURED)
+                               ){
+                                       __u8 *ptr;
+
+                                       obj=dev->candev->chip[dev->rcv_msg[0]]->msgobj[0];
+
+                                       len=*(uint8_t *)(dev->rcv_msg+1);
+                                       if(len > CAN_MSG_LENGTH) len = CAN_MSG_LENGTH;
+                                       obj->rx_msg.length = len;
+
+                                       obj->rx_msg.flags=le16_to_cpu(*(uint16_t *)(dev->rcv_msg+2));
+                                       obj->rx_msg.id=le32_to_cpu((*(uint32_t *)(dev->rcv_msg+4)));
+
+                                       for(ptr=dev->rcv_msg+8,i=0; i < len; ptr++,i++) {
+                                               obj->rx_msg.data[i]=*ptr;
+                                       }
+
+                                       // fill CAN message timestamp
+                                       can_filltimestamp(&obj->rx_msg.timestamp);
+                                       canque_filter_msg2edges(obj->qends, &obj->rx_msg);
+                               }
+                       }
+    }
+  }
+  /* here we go only in case of termination of the thread */
+error:
+  /* cleanup the thread, leave */
+  CANMSG ("kernel thread terminated!\n");
+  exit_kthread(kthread);
+
+  /* returning from the thread here calls the exit functions */
+}
+
+static int usbcan_probe(struct usb_interface *interface, const struct usb_device_id *id)
+{
+       struct usbcan_usb *dev;
+       struct usb_host_interface *iface_desc;
+       struct usb_endpoint_descriptor *endpoint;
+       size_t buffer_size;
+       int i;
+       int retval = -ENOMEM;
+
+       /* allocate memory for our device state and initialize it */
+       dev = (struct usbcan_usb *) can_checked_malloc(sizeof(struct usbcan_usb));
+       if (!dev) {
+               err("Out of memory");
+               goto error;
+       }
+
+       sema_init(&dev->limit_sem, WRITES_IN_FLIGHT);
+       spin_lock_init(&dev->err_lock);
+       init_usb_anchor(&dev->submitted);
+
+//     dev->udev = usb_get_dev(interface_to_usbdev(interface));
+       dev->udev = interface_to_usbdev(interface);
+       dev->interface = interface;
+
+       /* set up the endpoint information */
+       /* use only the first bulk-in and bulk-out endpoints */
+       iface_desc = interface->cur_altsetting;
+       for (i = 0; i < iface_desc->desc.bNumEndpoints; ++i) {
+               endpoint = &iface_desc->endpoint[i].desc;
+
+               if (!dev->bulk_in_endpointAddr &&
+                   usb_endpoint_is_bulk_in(endpoint)) {
+                       /* we found a bulk in endpoint */
+                       buffer_size = le16_to_cpu(endpoint->wMaxPacketSize);
+                       dev->bulk_in_size = buffer_size;
+                       dev->bulk_in_endpointAddr = endpoint->bEndpointAddress;
+                       dev->bulk_in_buffer = can_checked_malloc(buffer_size);
+                       if (!dev->bulk_in_buffer) {
+                               err("Could not allocate bulk_in_buffer");
+                               goto error;
+                       }
+               }
+
+               if (!dev->bulk_out_endpointAddr &&
+                   usb_endpoint_is_bulk_out(endpoint)) {
+                       /* we found a bulk out endpoint */
+                               dev->bulk_out_endpointAddr = endpoint->bEndpointAddress;
+               }
+
+               if (!dev->ctl_in_endpointAddr &&
+                   usb_endpoint_xfer_control(endpoint) &&
+                   usb_endpoint_dir_in(endpoint)) {
+                       /* we found a bulk in endpoint */
+                       buffer_size = le16_to_cpu(endpoint->wMaxPacketSize);
+                       dev->ctl_in_size = buffer_size;
+                       dev->ctl_in_endpointAddr = endpoint->bEndpointAddress;
+                       dev->ctl_in_buffer = can_checked_malloc(buffer_size);
+                       if (!dev->ctl_in_buffer) {
+                               err("Could not allocate bulk_in_buffer");
+                               goto error;
+                       }
+               }
+
+               if (!dev->ctl_out_endpointAddr &&
+                   usb_endpoint_xfer_control(endpoint) &&
+                   usb_endpoint_dir_out(endpoint)) {
+                       /* we found a bulk out endpoint */
+                               dev->ctl_out_endpointAddr = endpoint->bEndpointAddress;
+               }
+       }
+       if (!(dev->bulk_in_endpointAddr && dev->bulk_out_endpointAddr)) {
+               err("Could not find all bulk-in and bulk-out endpoints");
+               goto error;
+       }
+
+       /* save our data pointer in this interface device */
+       usb_set_intfdata(interface, dev);
+
+       register_usbdev("usbcan",(void *) dev);
+
+       /* let the user know what node this device is now attached to */
+       info("USB Skeleton device now attached");
+       return 0;
+
+error:
+       usb_put_dev(dev->udev);
+       if (dev->bulk_in_buffer)
+               can_checked_free(dev->bulk_in_buffer);
+       if (dev->ctl_in_buffer)
+               can_checked_free(dev->ctl_in_buffer);
+       if (dev->candev){
+               dev->candev->sysdevptr.anydev=NULL;
+               cleanup_usbdev(dev->candev);
+       }
+       can_checked_free(dev);
+       return retval;
+}
+
+// Physically disconnected device
+static void usbcan_disconnect(struct usb_interface *interface)
+{
+       struct usbcan_usb *dev;
+       int minor = interface->minor;
+
+       dev = usb_get_intfdata(interface);
+       usb_set_intfdata(interface, NULL);
+
+       /* prevent more I/O from starting */
+       mutex_lock(&dev->io_mutex);
+       dev->interface = NULL;
+       mutex_unlock(&dev->io_mutex);
+
+       //usb_kill_anchored_urbs(&dev->submitted);
+
+       usb_put_dev(dev->udev);
+       if (dev->bulk_in_buffer)
+               can_checked_free(dev->bulk_in_buffer);
+       if (dev->ctl_in_buffer)
+               can_checked_free(dev->ctl_in_buffer);
+       if (dev->candev){
+               dev->candev->sysdevptr.anydev=NULL;
+               cleanup_usbdev(dev->candev);
+       }
+       can_checked_free(dev);
+
+       info("USB Skeleton now disconnected");
+}
+
+int usbcan_init(void){
+       return usb_register(&usbcan_driver);
+}
+
+void usbcan_exit(void){
+       usb_deregister(&usbcan_driver);
+}