dbnet.home Bookmark and Share

MEET FEATURE REQUIREMENTS, SCHEDULE, and BUDGET! Consulting available to teach your organization to apply this methodology and tools for powerful quantitative management of your business processes.

  • Instruction of your staff at your site, using courseware, application example, and a functional template.
  • Mentoring your key staff on an ongoing or periodic basis, on these tools or on Quantitative Program Management.
  • Contracting or Employment in your organization on specific topics.

Brochure  ...  Contact for Details

Check out my YouTube Channel: Power Operational Intelligence

Now Live! Overview, Structure, Task Data, Table Design, SQL Server, and Re-Linking now showing.

Video courses covering material on this website, and more, are presented in the playlists.

Code snippet links at YouTube Code Snippets. Twitter at @poweroperation1, #poweropi, #poweroperationalintelligence.

Subscribe on YouTube, and click the "Notification" Bell icon to be notified as content is published.

VBA Access to Structured Tables Using Structured References and/or Excel Objects

2019 July 31 - Updated to describe use of VBA WorksheetFunction, which may be the best option for Structured Reference in VBA using supported functions, which include key functions INDEX, MATCH, and SUMIF.

Use of Structured References in the Excel User Interface to link Tables and to provide field calculations raises the level of design thinking up from cells and worksheets to Tables, Records and Fields. This design level in Excel uses data relationships that are independent of "fixed" locations of Cells and Worksheets. But what if you need to access Structured Table data from VBA?

In the upcoming descriptions, we will use INDEX-MATCH, SUMIF, TEXTJOIN and FOREACH structures commonly used in Excel Structured Table references, to show how VBA semantics can directly incorporate Structured References by using the VBA Application.WorksheetFunction function, the VBA EVALUATE function, and also show VBA semantics using the Excel Object Model to perform these operations. When a new function is introduced to Excel, its VBA WORKSHEETFUNCTION equivalent function may not be available until a much later release, which is why we also show the EVALUATE and VBA syntax to accomplish several functions below. Syntax is shown for XLOOKUP and XMATCH as well, on the Programming Projects page on this site.

Excel provides three ways to address Structured References from within VBA, with varying similarity to use of Structured References in the Excel User Interface:

  • Excel Object Model: Structured Tables are represented by Worksheet.ListObject, itself containing TableObject, HeaderRowRange, DatabodyRange, ListRows, ListColumns, Range and other objects useful for VBA emulation of Structured References. The provided objects must of course be set up for use navigating Structured Tables.
  • VBA WORKSHEETFUNCTION: Native functions for INDEX, MATCH, SUMIF, and TEXTJOIN are not provided. However, these functions are available via Application.WorksheetFunction and using these together with the Worksheet.ListObject objects, you can emulate Structured References quite well. Not all functions are available via WorksheetFunction, but the functions key to Structured Table navigation, as just listed, are available and you can emulate Structured References using VBA function calls.
  • VBA EVALUATE function: This VBA function supports use of Structured References almost as closely as copy-paste from the Excel User Interface. The expressions are represented as text strings rather than by function calls. Care must be taken with quote-symbols when representing quoted strings within the expression, and when inserting VBA variables to provide values within the string. WorksheetFunction may be preferred over Evaluate, perhaps a matter of preference; but for any function not available to VBA, or for a reference that proves difficult to set up, EVALUATE can be used to provide a direct analog to Structured Reference.

The declarations shown at the top of the code figure below of course apply to all the following examples. Within the examples, Excel is Blue italic. The Structured Table referenced in the examples is shown at the bottom of this page.

Dim wksThisWorksheet As Worksheet
Dim rsltINDEXMATCH As Variant, varINDEXMATCHResult As Variant, varFUNCMATCHResult As Variant
Dim rsltSUMIF As Double, rsltPriceSF As Double
Dim intRowNum As Integer, intColNum As Integer
Dim cellValue As String, strTargetValue As String, expr As String, strQuotTargetValue As String
Dim strRsltColName As String, strSearchColName As String, strTableName As String
Dim strVBCONCATResult As String, concatColName As String
Dim objCellValue As Object, objRow As Object
Dim loTableListObject As ListObject, tblMaterial As ListObject
Dim thisRow As ListRow
Dim thisCol As ListColumn
Dim concatColRange As Range

Set wksThisWorksheet = ActiveWorkbook.Worksheets("Material") 'Initialization

INDEX-MATCH: VBA using Structured Reference

In the Excel User Interface, you might have a formula

=INDEX(tblMaterial, MATCH("Oslo Porcelain:Bronze:Gloss:Bronze", tblMaterial[MaterialKey],0), MATCH("Price$SF", tblMaterial[#Headers], 0))

Using WORKSHEETFUNCTION: Set up the objects as shown, and call the INDEX and MATCH WorksheetFunctions:

strTableName = "tblMaterial"
strSearchColName = "MaterialKey"
strTargetValue = "Oslo Porcelain:Bronze:Gloss:Bronze"
strRsltColName = "Price$SF"
Set tblMaterial = wksThisWorksheet.ListObjects(strTableName)
Set tblMaterialRange = tblMaterial.Range
Set searchColumn = tblMaterial.ListColumns(strSearchColName).Range
Set headerRow = tblMaterial.HeaderRowRange

With Application.WorksheetFunction
	rsltINDEXMATCH = .Index(tblMaterialRange, .Match(strTargetValue, searchColumn, 0), _
			.Match(strRsltColName, headerRow, 0))

End With
							

The result closely emulates the structure of an Excel User Interface - Structured Reference expression, even if not its syntax.

Using EVALUATE: Equivalent VBA encapsulates the structured reference within Quotes as the argument of an EVALUATE function:

rsltINDEXMATCH = Evaluate("INDEX(tblMaterial, MATCH(""Oslo Porcelain:Bronze:Gloss:Bronze"", _
    tblMaterial[MaterialKey],0), MATCH(""Price$SF"", tblMaterial[#Headers], 0))")

You can see the argument to the EVALUATE function is almost identical to the Excel expression: INDEX(tblMaterial, MATCH("Oslo Porcelain:Bronze:Gloss:Bronze", tblMaterial[MaterialKey],0), MATCH("Price$SF", tblMaterial[#Headers], 0)). That expression is provided as a string, surrounded by QUOTE characters to indicate that to VBA.

The exceptions deal with how the string value deals with quoted values within it. The Excel Structured Reference uses literal quoted values "Oslo Porcelain:Bronze:Gloss:Bronze" and "Price$SF" as arguments. So within the string argument to be passed to the EVALUATE function, double-quote escape-characters are required in order to force quote-symbols within the quoted string argument. The argument to the EVALUATE function is therefore "INDEX(tblMaterial, MATCH(""Oslo Porcelain:Bronze:Gloss:Bronze"", tblMaterial[MaterialKey],0), MATCH(""Price$SF"", tblMaterial[#Headers], 0))" including the surrounding quotes telling VBA that it is a string and the internal double-quotes indicating the single-quote characters to be included within the string value.

That argument is evaluated by VBA before being passed into the EVALUATE, the evaluated value passed to the function being INDEX(tblMaterial, MATCH("Oslo Porcelain:Bronze:Gloss:Bronze", tblMaterial[MaterialKey],0), MATCH("Price$SF", tblMaterial[#Headers], 0)), a string value without surrounding quote characters, and evaluating the double-quote characters within as single-quote characters within the string value, so the value of the string exactly matches the intended Excel Structured Reference INDEX(tblMaterial, MATCH("Oslo Porcelain:Bronze:Gloss:Bronze", tblMaterial[MaterialKey],0), MATCH("Price$SF", tblMaterial[#Headers], 0)).

SUMIF: VBA using Structured Reference

In the Excel User Interface, you might have a formula

=SUMIF(tblMaterial[MaterialKey], "Imperial Next:Bardiglio:Satin:Grey Marble", tblMaterial[Price$SF])

Using WORKSHEETFUNCTION: Again, set up the objects, and call the SUMIF WorksheetFunction.

Set tblMaterial = wksThisWorksheet.ListObjects("tblMaterial")
'strSearchColName string is set above
'strRsltColName string is set above
Set searchColumn = tblMaterial.ListColumns(strSearchColName).Range
Set SumColumn = tblMaterial.ListColumns(strRsltColName).Range

With Application.WorksheetFunction
    rsltSUMIF = .SumIf(searchColumn, strTargetValue, SumColumn)

End With
							

Again, the result closely emulates the structure of the Excel UI call, although not the syntax.

Using EVALUATE: Similarly for SUMIF, you can use Structured Reference syntax, by using VBA EVALUATE function:

Equivalent VBA using an EVALUATE function:

rsltSUMIF = Evaluate("SUMIF(tblMaterial[MaterialKey], _
    ""Imperial Next:Bardiglio:Satin:Grey Marble"", tblMaterial[Price$SF])")

Once again, you can see the Excel Structured Reference, enclosed in quotes and with double-quote characters indicating quote characters to be included within the string to be passed as the argument to EVALUATE.

Concatenating a VBA Variable into the Structured Reference argument of VBA EVALUATE

The value of an argument may be set in a VBA variable by a statement outside the EVALUATE expression. That requires concatenating the variable into the quoted reference argument of EVALUATE. Excel:

=SUMIF(tblMaterial[MaterialKey], strTargetValue, tblMaterial[Price$SF])

Equivalent VBA using an EVALUATE function, and concatenating in the variable "strTargetValue":

'Build the expression to EVALUATE, outside of the EVALUATE call
strTargetValue = "Imperial Next:Bardiglio:Satin:Grey Marble"
expr = "SUMIF(tblMaterial[MaterialKey], """ & strTargetValue & """, _
    tblMaterial[Price$SF])"
rsltSUMIF = Evaluate(expr)

In the expr expression building up the Structured Reference, the variable strTargetValue will be evaluated to its value Imperial Next:Bardiglio:Satin:Grey Marble (text string that won't include quotes) so the initial part of the Structured Reference expression (the part preceding concatenation of the variable into the argument) must include a quote symbol, forced by the double-quote, and then that part of the Structured Reference is concluded by its quote symbol - resulting in the triple-quote """.

That initial part of the Structured Reference is then concatenated with the evaluated value of variable strTargetValue using "&" operators.

Finally, the part of the Structured Reference following the concatenation of the variable value must begin with a quote symbol to finish quoting the evaluated variable strTargetValue, so a double-quote symbol is placed inside the leading quote of the last part of the Structured Reference - resulting a leading """.

The resulting string, is evaluated by VBA to pass the string value to EVALUATE, as Excel Structured Reference: SUMIF(tblMaterial[MaterialKey], "Imperial Next:Bardiglio:Satin:Grey Marble", tblMaterial[Price$SF]), identical to the preceding example.

Alternately, you could build the EVALUATE argument within the call:

strTargetValue = "Imperial Next:Bardiglio:Satin:Grey Marble"
rsltSUMIF = Evaluate("SUMIF(tblMaterial[MaterialKey], """ & strTargetValue & """, _
    tblMaterial[Price$SF])")

...or put the burden of quoting on the code that sets the value:

'Set strTargetValue, adding double-quote around the TargetValue
strQuotTargetValue = """Imperial Next:Bardiglio:Satin:Grey Marble"""

'Concatenate strTargetValue into the SUMIF EVALUATE.
rsltSUMIF = Evaluate("SUMIF(tblMaterial[MaterialKey], " & strQuotTargetValue & ", _
    tblMaterial[Price$SF])")

TEXTJOIN: VBA using Structured Reference

You could use Structured Reference syntax via VBA EVALUATE for small or sparse tables. My own use has been to concatenate Table cells that collectively contain Excel connection descriptors and SQL directives, as an example of a small table for which this is useful. Excel formula:

=TEXTJOIN(CHAR(10),True,tblMaterial[Item])

Note that the EVALUATE function argument is limited to 255 characters, otherwise a "Type mismatch" error is returned. Concatenating Table cells to create even a fairly short SQL expression can easily encounter this. You can avoid the problem by using WORKSHEETFUNCTION as shown just below, or by using the VBTEXTJOIN function farther down this page.

USING WORKSHEETFUNCTION:

concatColName = "Surface"
Set concatColRange = tblMaterial.ListColumns(concatColName).Range
Set concatColRange = Range(concatColRange(2), concatColRange(concatColRange.Count))
'Drop the column name included in concatColRange. VBA picks up the column name
'  in the ListColumn range, a difference from Excel.

With Application.WorksheetFunction
    strVBCONCATResult = .TextJoin(Chr(10), True, concatColRange)
	'Note use of CHR function in VBA vs CHAR function when TEXTJOIN is called
	'  from Excel User Interface, another difference from Excel.

End With
							

EQUIVALENT FUNCTION USING EVALUATE:

strTargetValue = Evaluate("TEXTJOIN(CHAR(10),True,tblMaterial[Item])")

The Excel Structured Reference, enclosed in quotes and with double-quote characters indicating quote characters is included within the string to be passed as the argument to EVALUATE.

Note for general use: the argument to EVALUATE is limited to 255 characters, and the content of the Structured Reference argument to TEXTJOIN is evaluated prior to the call to TEXTJOIN (to provide the STRING argument type required by TEXTJOIN) and may exceed 255 characters unless the table column contains few characters, resulting in a "Type mismatch" error. For this reason, a VBA substitute for TEXTJOIN using the Object Model that can be called from within VBA is provided below.

The VBA function "VBTEXTJOIN" is shown below. It can be called from an Excel expression including Structured Reference to a Structured Table column containing text values, and does not have the 255-character limit. Syntax for calling it from Excel is shown just below the VBA code defining the function. TEXTJOIN was introduced in Excel 2016 and the VBA function below may provide a substitute in earlier editions.

FOR-EACH: VBA SYNTAX to Scan Down a Structured Table examining Columns

Set wksThisWorksheet = Application.Worksheets("Material")
Set loTableListObject = wksThisWorksheet.ListObjects("tblMaterial")
intColNum = Application.WorksheetFunction.Match("MaterialKey", loTableListObject.HeaderRowRange, 0)

For Each thisRow In loTableListObject.ListRows
    cellValue = thisRow.Range.Cells(intColNum)
    If cellValue = "Imperial Next:Bardiglio:Satin:Grey Marble" Then
        'Act on targeted row
        rsltPriceSF = thisRow.Range.Cells(Application.WorksheetFunction.Match("Price$SF", _
            loTableListObject.HeaderRowRange, 0))

    End If
        
Next thisRow

FOR: VBA SYNTAX to Scan Down Structured Table Rows and Process each Row

Set wksThisWorksheet = Application.Worksheets("Material")
Set loTableListObject = wksThisWorksheet.ListObjects("tblMaterial")
intColNum = Application.WorksheetFunction.Match("MaterialKey", loTableListObject.HeaderRowRange, 0)

For intRowNum = 2 To loTableListObject.ListRows.Count   'Skip HeaderRowRange in Row 1
    'Now process data in the row selected by intRowNum
    cellValue = Application.WorksheetFunction.Index(loTableListObject.Range, _
        intRowNum, intColNum)
        
Next intRowNum

VBA USING EXCEL OBJECT MODEL

Functions below are shown as "Public" so that they can also be called from Excel formula expressions. If the functions are only to be called from VBA, these functions can be "Private".

INDEX-MATCH: VBA using Excel Object Model with WorksheetFunction

varINDEXMATCHResult = INDEXMATCH("Material", "tblMaterial", _
    "Imperial Next:Bardiglio:Satin:Grey Marble", _"MaterialKey", "Price$SF")

Public Function INDEXMATCH(ByVal strWksName As String, ByVal strTableName As String, _
        ByVal rowKeyVal As Variant, ByVal strRowKeyColName As String, _
        ByVal strColKeyName As String) As Variant

    Dim wksThisWorksheet As Worksheet
    Dim loTableListObject As ListObject
    Dim intRowNum As Integer, intColNum As Integer
    
    Set wksThisWorksheet = Application.Worksheets(strWksName)
    Set loTableListObject = wksThisWorksheet.ListObjects(strTableName)
    
    intRowNum = Application.WorksheetFunction.Match(rowKeyVal, _
        loTableListObject.ListColumns(strRowKeyColName).Range, 0)
    intColNum = Application.WorksheetFunction.Match(strColKeyName, _
        loTableListObject.HeaderRowRange, 0)
    
    INDEXMATCH = Application.WorksheetFunction.Index(loTableListObject.Range, intRowNum, intColNum)
    
End Function

SUMIF, COUNTIF: VBA using Excel Object Model with Structured Reference and EVALUATE

varFUNCMATCHResult = FUNCIF("SUMIF", "Material", "tblMaterial", "MaterialKey", _
    "Marmi:Imperiali:Gloss:Grey-Tan", "Price$SF")

Public Function FUNCIF(ByVal funcName As String, strWksName As String, _
        ByVal strTableName As String, ByVal strCriteriaColName As String, _
        ByVal strCriteriaValue As Variant, ByVal strFuncValueColName As Variant)

    Dim wksThisWorksheet As Worksheet
    Dim loTableListObject As ListObject
    Dim FuncIfStr As String
    Dim test As Variant
    
    Set wksThisWorksheet = Application.Worksheets(strWksName)
    Set loTableListObject = wksThisWorksheet.ListObjects(strTableName)
        
    If LCase(funcName) = "countif" Then
        FuncIfStr = funcName & "(" & strTableName & "[" & strCriteriaColName & "], """ & _
            strCriteriaValue & """)"
    
    Else
        FuncIfStr = funcName & "(" & strTableName & "[" & strCriteriaColName & "], """ & _
            strCriteriaValue & """, " & strTableName & "[" & strFuncValueColName & "])"
    
    End If
    
    FUNCIF = Evaluate(FuncIfStr)
    
End Function

TEXTJOIN: VBA using Excel Object Model

2020 May 1: Updated VBTEXTJOIN to eliminate strCRLFChar character at the end of the last line concatenated from the rngColConcat source text argument. Now the algorithm prepends strCRLFChar rather than postpending it.

If you call the Excel TEXTJOIN function in VBA using EVAL, you may encounter the EVAL 255-character limit. You could avoid that by calling APPLICATION.WORKSHEETFUNCTION.TEXTJOIN. Or you could use the following VBTEXTJOIN which emulates TEXTJOIN, avoids the 255-character limit to the rngColConcat argument, and adds some features that are convenient for concatenating SQL strings. The strCRLFChar argument is a string, and can add more function than CRLF at the end of each line concatenated. VBTEXTJOIN also ignores blank lines in a Structured Table passed in argument rngColConcat preceding the first non-blank line, ignores blank lines following the last blank line, but maintains blank lines within the non-blank region to preserve spacing among non-blank lines.

Note also that in the function call example (strVBCONCATResult line near the top of the code below), the strCRLFChar is set as a space concatenated with a vbCRLF character, to improve readability of strings to be passed to SQL by inserting both a space and a vbCRLF at end of line. This displays a space at the end of each line which improves readability of the concatenated SQL string result when it is viewed in a context that does not display line feeds. This does not affect SQL functionality. Including such a space character is optional of course, and its utility is entirely dependent on use of the strVBCONCATResult result from VBTEXTJOIN. The same can be done in Excel, using CHAR(32) & CHAR(10) in the function call from Excel.

Set wksThisWorksheet = Application.Worksheets("Material")
Set loTableListObject = wksThisWorksheet.ListObjects("tblMaterial")
strVBCONCATResult = VBTEXTJOIN(chr(32) & Chr(10), True, _
        loTableListObject.ListColumns("MaterialKey").Range, "VBA")

Public Function VBTEXTJOIN(ByVal strCRLFChar As String, ByVal bIgnoreBlank As Boolean, _
        ByVal rngColConcat As Range, ByVal calledFrom As String) As String
    'Replicate Excel2016 TEXTJOIN function, in VB
    Dim thisString As String
    Dim objThisString As Object
    Dim bColumnLabel As Boolean
    Dim intColConcatIndex As Integer, intColConcatIndexLast As Integer
    
    Select Case LCase(calledFrom)
        Case "excel"
            bColumnLabel = False
        Case "vba"
            bColumnLabel = True
        Case Else
            bColumnLabel = False
    End Select
    'Set bColumnLabel to ignore first element of rngColConcat if the call is from VBA.
    'rngColConcat as tablename[columnname] from Excel does not include columnname
    '   as first element.
    'rngColConcat as loTableListObject.ListColumns("MaterialKey").
    ' Range includes columnname as first element.
    
    intColConcatIndexLast = rngColConcat.Count
    ' Find last non-empty cell
    For intColConcatIndex = rngColConcat.Count To 1 Step -1
        thisString = rngColConcat(intColConcatIndex)
        If Not ((thisString = "" Or IsNull(thisString)) And bIgnoreBlank) Then
                intColConcatIndexLast = intColConcatIndex
                Exit For
        End If
        
    Next intColConcatIndex
    
    VBTEXTJOIN = ""
    For intColConcatIndex = 1 To intColConcatIndexLast
        If bColumnLabel Then
            bColumnLabel = False
        Else
            thisString = rngColConcat(intColConcatIndex)
            
            ' Ignore empty cells above first non-blank cell
            If VBTEXTJOIN = "" And Not ((thisString = "" Or IsNull(thisString)) _
                            And bIgnoreBlank) Then
                    ' Add first non-blank cell to return value
                    VBTEXTJOIN = thisString
                
            Else
                ' Add blank or non-blank cells after first non-blank cell,
                    'added value preceded by a CRLF character
                VBTEXTJOIN = VBTEXTJOIN & strCRLFChar & thisString
            
            End If
            
        End If
        
    Next intColConcatIndex
    
End Function
    

Note in the above code that the call to VBTEXTJOIN from within VBA includes the argument "calledFrom" with value "VBA". You probably don't want to include the column name cell in the string result when TEXTJOINing a column of values in a Structured Table. A call from VBA passes the rngColConcat argument as a ListObject.Column range which includes the column name, whereas an Excel call passing in a StructuredTable["columnname"] range does not include the column heading cell. The calledFrom argument controls whether the first element of the range will be ignored as would be typical in a call from VBA, or concatenated with the rest of the range elements as would be typical in a call from Excel.

The VBTEXTJOIN function can be called from an Excel formula expression as

=VBTEXTJOIN(CHAR(10),True,tblMaterial[Item],"EXCEL") or
=VBTEXTJOIN(CHAR(32) & CHAR(10),True,tblMaterial[Item],"EXCEL") to put a space and a CRLF character (or any such combination defined in the strCRLFChar argument) after each element concatenated from the rngColConcat argument.


XLOOKUP: VBA to Return a Single Structured Table Column by Name

The Excel XLOOKUP function is available AFTER Excel versions 2016 and 2019. So you or your users may not have the function available. Following is VBA emulation of a specific use: return of a column with a specified name, from a Structured Table.

This function allows each destination Structured Table record (the one doing the lookup) to specify the name of a Column (probably in another Table), naming the Column via a field in the destination Table so that the Column name is not hard-coded into each reference.

You could always use construct "tblTableName[ColumnName]" (ColumnName is hard-coded in the call), but that puts column name in the function call rather than in a data value in the Table. Function vbatableXLOOKUP makes it possible for each record to specify its needed column via drop-down, or calculation, etc.

Public Function vbatableXLOOKUP(ByVal varLookupValue As Variant, ByVal rngTableLookupRange As Range,_
         ByVal rngTableReturnArray As Range) As Range
' Emulation of XLOOKUP return of a column in a table, with a specified column heading.
' Call syntax in a Structured Table: vbatableXLOOKUP([@columnName], tableName[#Headers],tableName[#Data])
' Call syntax for XLOOKUP almost identical:  XLOOKUP([@columnName], tableName[#Headers],tableName[#Data])
    Dim intMatchType As Integer
    Dim intMatchColNum As Integer
    
    intMatchType = 0 ' 0 for EQ; -1 for GE; 1 for LE
    intMatchColNum = WorksheetFunction.Match(varLookupValue, rngTableLookupRange, intMatchType)
    Set vbatableXLOOKUP = rngTableReturnArray.Columns(intMatchColNum)
    
End Function

Structured Table Referenced in Example VBA

images/TileTableExample.jpg


Example Structured Table VBA Source

Source for example code above: VBA Table Expressions. Code in the examples has been modified to fit this website pagewidth.