Using Excel Visual Basic for Applications with Kvaser CANlib

  • April 7, 2022
  • Dan Arvidson

Most of us have Microsoft Office installed on our Windows PC and we use Microsoft Excel for lists and calculations, but did you know that you can:

  1. Send data from any cell in your Excel sheet on the CAN bus.
  2. Receive data from the CAN bus to any cell in Excel.

Kvaser CANlib can be used in Visual Basic for Applications (VBA). This versatile library supports every Kvaser CAN interface and allows you to write advanced and innovative solutions.

So why use VBA when there are so many other languages available? First, it is available to you already if you have Microsoft Office and it is relatively easy to start with. Excel is broadly used and by using its VBA you will have everything that Excel offers, together with your own creative and innovative ideas. If you already have and use Excel, then the cost is of course one thing that comes to my mind as well. Data is easily shared within the organization; many companies have a process involving Microsoft file formats.

What do I need to use this blog?

To follow the steps in this blog article and to use Excel VBA with Kvaser CANlib you’ll need to have a version of Microsoft Office installed. It doesn’t matter which version of Microsoft Office you have but preferably, it is at least Office 2010 since that is when VBA 7 was introduced. Both 64-bit and 32-bit Office works (please see chapter 2.2 32 vs 64-bit Microsoft Office). I have used Office 365 with Excel version 2202 Build 16.0.14931.20116) 64-bit when writing this.

You also need to have “Kvaser Drivers for Windows” installed. Please find the latest version available here: https://www.kvaser.com/download/ and follow the step-by-step installation guide. 

Nothing else is required, but if you want to go deeper and further with CANlib, I do recommend you to download the “Kvaser CANlib SDK”, also available from the same download page.


Introduction

Visual Basic for Applications (VBA) is an event-driven programming language used by Microsoft to extend their Office applications. With VBA, you can extend processes with automation, Windows APIs and custom functions. You can also control the user interface features of the host application.

VBA is an implementation of Microsoft’s programming language Visual Basic 6 and it uses a stripped down version of that same editor together with similar debugging capabilities. So, if you know VB6, you’ll also know your way around in VBA. Visual Basic was created to simplify programming, which means that programming in VBA is not hard, it uses English-like statements in order to tell the computer what to do.

Application.ActiveDocument.SaveAs ("New Document Name.docx")

Save the active document as “New Document Name.docx”.

Worth mentioning is that VBA is single threaded, which means that it will execute one task at a time. Please read more about this in chapter 2.3 Multitasking.

Office does not show the Developer tab by default, you must enable it:

  • From the File tab, select Options to open the Options dialog box.
  • Select “Customize Ribbon” on the left side of the dialog box.
  • In “Choose Commands From” on the left side of the dialog box, select “Common Commands”.
  • In “Customize the ribbon” on the right side, select “Main Tab” from the drop-down list, and then check the “Developer” box.
  • Select OK.

From the developer tab you can open the editor and create buttons, drop-down menus etc. There is also a shortcut to just open the editor from anywhere in an Office application: ALT+F11.

The VBA community is really large. Searching the Internet will almost always give you a VBA example that does, if not exactly, at least something similar to what you want to do.


VBA Example

The first example will show how to react when a certain cell is changed and send that value on the CAN bus.

In the VBA editor double click on the sheet where the cell is located that you want to react on and select the “Change” procedure for that worksheet.

image4

The worksheet change event will execute every time something changes in that sheet and to narrow it to a specific cell, I use the Intersect() function in VBA. This function determines whether the changed cell “intersects” with the cell we have specified. To simplify the example I assume that the worksheet is active and that the value we want to send is in between 0-255. For more information about the arguments used in canWrite and how to receive data from the CAN bus, please follow on to the next example.  

In my other example I have imported a log file into Excel (in my case it is an .ASC file). I do this just to have data to send on the CAN bus.

image3

Your data can of course come from any source, opening a file in VBA, have a few specific frames written in Excel that always should be sent etc.

I won’t go through CANlib very thoroughly. This example is simply to give you a hint of what’s possible when it comes to VBA and CANlib.

I will show how to send data from any cell in Excel and how to receive data into any cell in Excel, using Kvaser CANlib.


Code

CANlib API- and handles declaration

Option Explicit 'Force explicit variable declaration so that an undeclared variable generates error.
 
 
#If VBA7 Then
  Private Declare PtrSafe Sub canInitializeLibrary Lib "CANLIB32.DLL" ()
  Private Declare PtrSafe Function canUnloadLibrary Lib "CANLIB32.DLL" () As Long
  Private Declare PtrSafe Function canGetNumberOfChannels Lib "CANLIB32.DLL" (ByRef channelCount As Long) As Long
  Private Declare PtrSafe Function canGetChannelData Lib "CANLIB32.DLL" (ByVal channel As Long, ByVal item As Long, ByRef buffer As Any, ByVal bufsize As Long) As Long
  Private Declare PtrSafe Function canOpenChannel Lib "CANLIB32.DLL" (ByVal handle As Long, ByVal Flags As Long) As LongPtr
  Private Declare PtrSafe Function canClose Lib "CANLIB32.DLL" (ByVal handle As LongPtr) As Long
  Private Declare PtrSafe Function canBusOn Lib "CANLIB32.DLL" (ByVal handle As LongPtr) As Long
  Private Declare PtrSafe Function canBusOff Lib "CANLIB32.DLL" (ByVal handle As LongPtr) As Long
  Private Declare PtrSafe Function canSetBusParams Lib "CANLIB32.DLL" (ByVal handle As LongPtr, ByVal freq As Long, ByVal tseg1 As Long, ByVal tseg2 As Long, ByVal sjw As Long, ByVal noSamp As Long, ByVal syncMode As Long) As Long
  Private Declare PtrSafe Function canWrite Lib "CANLIB32.DLL" (ByVal handle As LongPtr, ByVal id As Long, ByRef msg As Any, ByVal dlc As Long, ByVal flag As Long) As Long
  Private Declare PtrSafe Function canReadWait Lib "CANLIB32.DLL" (ByVal handle As LongPtr, ByRef id As Long, ByRef msg As Any, ByRef dlc As Long, ByRef flag As Long, ByRef time As Long, ByRef timeout As Long) As Long
#Else
  Private Declare Sub canInitializeLibrary Lib "CANLIB32.DLL" ()
  Private Declare Function canUnloadLibrary Lib "CANLIB32.DLL" () As Long
  Private Declare Function canGetNumberOfChannels Lib "CANLIB32.DLL" (ByRef channelCount As Long) As Long
  Private Declare Function canGetChannelData Lib "CANLIB32.DLL" (ByVal channel As Long, ByVal item As Long, ByRef buffer As Any, ByVal bufsize As Long) As Long
  Private Declare Function canOpenChannel Lib "CANLIB32.DLL" (ByVal handle As Long, ByVal Flags As Long) As Long
  Private Declare Function canClose Lib "CANLIB32.DLL" (ByVal handle As Long) As Long
  Private Declare Function canBusOn Lib "CANLIB32.DLL" (ByVal handle As Long) As Long
  Private Declare Function canBusOff Lib "CANLIB32.DLL" (ByVal handle As Long) As Long
  Private Declare Function canSetBusParams Lib "CANLIB32.DLL" (ByVal handle As Long, ByVal freq As Long, ByVal tseg1 As Long, ByVal tseg2 As Long, ByVal sjw As Long, ByVal noSamp As Long, ByVal syncMode As Long) As Long
  Private Declare Function canWrite Lib "CANLIB32.DLL" (ByVal handle As Long, ByVal id As Long, ByRef msg As Any, ByVal dlc As Long, ByVal flag As Long) As Long
  Private Declare Function canReadWait Lib "CANLIB32.DLL" (ByVal handle As Long, ByRef id As Long, ByRef msg As Any, ByRef dlc As Long, ByRef flag As Long, ByRef time As Long, ByRef timeout As Long) As Long
#End If
 
'Constant declarations
Private Const canOK = 0
Private Const canOPEN_ACCEPT_VIRTUAL = &H20
Private Const canBITRATE_250K = -3
Private Const canCHANNELDATA_CARD_SERIAL_NO = 7
 
 
'Declaration of CAN handles
#If VBA7 Then
  Private hnd0, hnd1 As LongPtr
#Else
  Private hnd0, hnd1 As Long
#End If

The declarations are required in order to specify which dll calls should be available and point out where this dll is located. CANlib32.dll is in the system path when installed through Kvaser’s installer. This means that you will not have to specify exactly where it is located.

[ Public | Private ] Declare Sub name Lib “libname” [ ( [ arglist ] ) ]
[ Public | Private ] Declare Function name Lib “libname” [ ( [ arglist ] ) ] [ As type ]

Using Private tells that this will only be accessible in the module where it is declared. 

The Kvaser CANlib SDK doesn’t include any VB or VBA declarations at this moment, so you’ll have to write these as needed. For the online Kvaser CANlib SDK please go to: https://www.kvaser.com/canlib-webhelp/index.html

You can of course contact me or our support and we will try to do our best to help you. The contact information is available at the end of this article.


Calling CANlib API

Initialize CANlib and get the number of available channels

Sub CANLib_Start()
  Dim chCount, stat, i As Long
  Dim buffer As String
  Dim myArr(32) As Byte
  Dim ws As Worksheet
	
  canInitializeLibrary
  stat = canGetNumberOfChannels(chCount)
  If stat <> canOK Then GoTo ErrorHandler

The canInitializeLibrary function must be called before any other functions are used. It will initialize the driver.

canGetNumberOfChannels, this function returns the number of available CAN channels in the computer. The virtual channels are included in this number.

Prepare the workbook for reading out some device information

Sheets.Add(Before:=Sheets(1)).name = "Device info" ' Add a sheet called "Device info" to the first position
 
Range("A1").Value = "Nof channels"
Range("B1").Value = chCount

Here we add a new sheet to the first position and write how many channels that we have available in cell B1 of that sheet.

Read some device information for each channel available

For i = 0 To chCount - 1
  stat = canGetChannelData(i, canCHANNELDATA_CARD_SERIAL_NO, myArr(0), 32)
  buffer = StrConv(myArr(), vbUnicode)
  If buffer <> Empty Then
    Cells(i + 2, 1).Value = "Serial"
    Cells(i + 2, 2).Value = buffer
  End If
Next i

Here we go through every available channel and ask for the device’s serial number, which we write to a new row for each channel in the second column (i.e. “B”).  

Open channels, set parameters and go bus on

hnd0 = canOpenChannel(0, canOPEN_ACCEPT_VIRTUAL)
hnd1 = canOpenChannel(1, canOPEN_ACCEPT_VIRTUAL)
stat = canSetBusParams(hnd0, canBITRATE_250K, 0, 0, 0, 0, 0)
If stat <> canOK Then GoTo ErrorHandler
stat = canSetBusParams(hnd1, canBITRATE_250K, 0, 0, 0, 0, 0)
If stat <> canOK Then GoTo ErrorHandler
	
stat = canBusOn(hnd0)
If stat <> canOK Then GoTo ErrorHandler
stat = canBusOn(hnd1)
If stat <> canOK Then GoTo ErrorHandler

Here we open the first and second channel to get the required handles needed in all other calls. We also prepare the two opened channels by setting them to the same bit rate.  

Prepare a sheet for read data

DeleteSheet ("Read data")
Set ws = Sheets.Add()
ws.name = "Read data"
ws.Cells(1, 1).Value = "ID"
ws.Cells(1, 2).Value = "Data1"
ws.Cells(1, 3).Value = "Data2"
ws.Cells(1, 4).Value = "Data3"
ws.Cells(1, 5).Value = "Data4"
ws.Cells(1, 6).Value = "Data5"
ws.Cells(1, 7).Value = "Data6"
ws.Cells(1, 8).Value = "Data7"
ws.Cells(1, 9).Value = "Data8"

Here we prepare a sheet to store the read data. I first delete the “Read data”-sheet in case it already exists. I then create the sheet and name it, whilst also adding some headlines so as to better understand the output. 

Send, receive, and populate cells

Sub CANlib_Traffic()
  Dim tb As ListObject
  Dim iCol, iRow As Integer
  Dim sData(1 To 8), sCol As String
  Dim bDataTx(1 To 8) As Byte
  Dim bDataRx(1 To 8) As Byte
  Dim stat, lID, lDlc, lFlags, lTime As Long
	
	
  Worksheets("Imported ASC").Activate
  Set tb = ActiveSheet.ListObjects("TestLog")
 
  For iRow = 1 To tb.Range.Rows.Count
    lDlc = tb.DataBodyRange.Cells(iRow, tb.ListColumns("DLC").Index) ' Get how many data bytes
    For iCol = 1 To lDlc
      sCol = "Data" + Trim(Str(iCol)) 'Create the headline to read from
      sData(iCol) = tb.DataBodyRange.Cells(iRow, tb.ListColumns(sCol).Index)
      bDataTx(iCol) = CByte("&H" & sData(iCol)) ' Convert the Hex value to decimal
    Next iCol
    ' Send the byte stream of CAN data on the first channel   	
    stat = canWrite(hnd0, CLng(iRow), bDataTx(1), lDlc, 0)
    DoEvents
    ' Read out the received data on the second channel
    stat = canReadWait(hnd1, lID, bDataRx(1), lDlc, lFlags, lTime, 50)
    If stat = canOK Then
      With Worksheets("Read data") ' Populate cells in Excel with read CAN data
        .Cells(lID + 1, 1).Value = lID
        ' .Cells(lID + 1, 2).Value = CStr(Hex(bDataRx(1))) ' Use this if value should be in hexadecimal
        .Cells(lID + 1, 2).Value = bDataRx(1)
        .Cells(lID + 1, 3).Value = bDataRx(2)
        .Cells(lID + 1, 4).Value = bDataRx(3)
        .Cells(lID + 1, 5).Value = bDataRx(4)
        .Cells(lID + 1, 6).Value = bDataRx(5)
        .Cells(lID + 1, 7).Value = bDataRx(6)
        .Cells(lID + 1, 8).Value = bDataRx(7)
        .Cells(lID + 1, 9).Value = bDataRx(8)
      End With
    End If
  Next iRow
	
  MsgBox "Traffic done!"
End Sub

First make sure the sheet from where we are going to read is activated. In my example I have named the table of imported data to “TestLog” which I set to a ListObject variable. I do this to make it easier to loop through when fetching values to be sent, by doing this I can use the table’s headlines to specify which column I’m reading from. The first loop is set to go through the complete range of imported data. I read the data length code (dlc) value to know how many bytes to read and later send. The second loop iterates through the data bytes, converts them from text formatted hex into decimal values and stores the values in a byte array.

The byte array of CAN data is then sent together with a message id (in this case the row number) and a data length code (dlc) by calling the CANlib function canWrite.

DoEvents makes it easier to stop the running macro. The DoEvents function enables interruption of executing code and lets the computer processor simultaneously run other tasks. Using DoEvents will slow the execution time down but will on the other hand give a chance to stop a running macro.

canReadWait reads a message from the receive buffer. If no message is available, the function waits until a message arrives or a timeout occurs.

Lastly I populate the previously created “Read data”-sheet with the read values. I use the message id to specify the cell row. By using a named sheet when writing to the cells I don’t have to activate that sheet (Worksheets(“Read data”).Cells(Row, Column).Value) and can keep the sheet holding imported data active.

Cleaning up afterwards

Sub CANLib_Stop()
  canBusOff (hnd0)
  canBusOff (hnd1)
  canUnloadLibrary
  MsgBox "CANlib is unloaded!"
End Sub

canBusOff will take the specified handle off-bus. If no other handle is active on the same channel, the channel will also be taken off-bus. canUnloadLibrary will free allocated memory, unload the DLLs canlib32.dll has loaded and de-initialize data structures.


Result

The result in this example looks like this:

image1

I could have chosen to have the output data formatted in hexadecimal for easier comparisons, then the cells would have been required to be formatted as text: ws.Columns(“A:I”).NumberFormat = “@” and when putting values into these cells, that would require a conversion like: Cells(col, row).Value = CStr(Hex(MyDecValue)).

But instead I chose to have it in decimal only to simplify further analysis. It is possible with hexadecimal values as well but would require a conversion at some point, since the chart objects in VBA and in Excel want their values to be in decimal format.

Excel graphs can be used to visualize the data, for example:

image2

Graphs can be made either in your VBA code or afterwards using the toolbar in Excel. For further and deeper understanding of what’s possible in VBA, please see Microsoft’s documentation: https://docs.microsoft.com/en-us/office/vba/api/overview/


32 vs 64-bit Microsoft Office

Both Office versions work fine, but worth mentioning is that in VBA version 7 some new 64-bit features were added.

vba ver 7

There are no unsigned data types in VBA, except for the data type Byte. But this is not a completely closed door – it is possible to read unsigned values in VBA, such as this example of how to use the Double type for values above 2147483647.

Private Const MAX_UINT32 = 4294967296#
Private Const MAX_INT32 = 2147483647
Function LongToUnsigned(ByVal Value As Long) As Double
  If Value < 0 Then
    LongToUnsigned = Value + MAX_UINT32
  Else
    LongToUnsigned = Value
  End If
End Function
 
Function UnsignedToLong(ByVal Value As Double) As Long
  If Value < 0 Or Value >= MAX_UINT32 Then Error 6
  If Value <= MAX_INT32 Then
    UnsignedToLong = Value
  Else
    UnsignedToLong = Value - MAX_UINT32
  End If
End Function

Multitasking

VBA is single threaded, which means that it’ll execute one task at a time. It is still possible to create a thread or use a callback function, like the kvSetNotifyCallback in CANlib, but I don’t recommend it. Creating one thread should probably be okay if it gets closed and waited for in the main thread, but creating more threads or trying to write to cells outside the main thread might cause Excel to freeze and shut down. To save you the headache and extra time, keep it simple and in the main thread.

For those with experience in VBA, there are ways to get round this, such as starting a new instance of Excel from within a loop in your code and call a procedure in your main workbook from that new instance.

My recommendation is to stay in the main thread.


Summary

In this article we have briefly looked into how to receive and send data on the CAN bus using CANlib and VBA in Microsoft Excel.  

I hope that this example has opened your eyes to what’s possible, even though it doesn’t cover Kvaser CANlib, VBA or Microsoft Excel that deeply.

Do you need more information or do you have questions?
Please feel free to contact us. Your comments and questions are welcome!
You can find us here:
[email protected]

Or, if you like, you can contact me directly:
Dan Arvidson
Customer Software Manager
[email protected]

namnlost-126-2

Dan Arvidson

N/A