You can use SQL to sum/average/find the min or max of values for data that you're grouped using a GROUP BY query in Microsoft Access. Alternatively you could use the less efficient built-in domain functions. Wouldn't it be nice if you could concatenate text fields in a similar manner.

The sample code in this article uses Microsoft Data Access Objects. For this code to run properly, you must reference the Microsoft DAO 3.X Object Library or Microsoft Office 16.0 Access database engine Object Library (use the most recent version). To do so, click References on the Tools menu in the Visual Basic Editor, and make sure that the appropriate Object Library reference check box is selected. Also, it uses the IsTableQuery() function.

So the idea is to take data like this:

Band Member
Metallica James Hetfield
Metallica Kirk Hammett
Metallica Lars Ulrich
Metallica Robert Trujillo
The Beatles John Lennon
The Beatles Paul McCartney
The Beatles George Harrison
The Beatles Ringo Starr

 

And turn it into this:

Band Members
Metallica James Hetfield, Kirk Hammett, Lars Ulrich, Robert Trujillo
The Beatles John Lennon, Paul McCartney, George Harrison, Ringo Starr

 

So I created a VBA function to do exactly this. And you'd use the following SQL:

Select Band, DConcat("tblData","Member","Band",[Band]) as ConcatenatedMembers 
From tblData

(I'll be the first to admit, this article isn't the most fun read.)

Note you pass the data source and 'field-to-concatenate' name as strings. Then the group-by field as string, then by actual 'field-to-concatenate' value from the data source.

Let's say you had two bands with the same name, but with different genres (and you had a genre field), then you'd use the following SQL:

Select Band, DConcat("tblData","Member","Band",[Band],"Genre",[Genre]) as ConcatenatedMembers 
From tblData

The idea is relatively simple. We pass the name of the table (or query) where all the data is from and the name of the field that we want to concatenate. I then use a ParamArray as the last argument of my function.

For those of you not familiar with using ParamArray, it is essentially a one dimensional dynamic array of data type variant. Using this, you can pass multiple arguments to a function. But you must be sure to declare this as the last argument in your function or procedure. See the VBA help file for more info.

I use the array to pass two pieces of data for each field that is used in the GROUP BY clause; the name of the field (string) and the value of the field (variant). It's a little work to have to type each field name but it's not too bad as long as you don't have too many fields in you GROUP BY clause.

I pass this info to the array in a certain order:
Field Name, Field Value, Field Name, Field Value, Field Name, Field Value, ...

So that number of elements in the paramarray must be even; i.e. double the number of fields used in the query's GROUP BY clause.

Then we create a SQL string to pull all records from the table or query that where the GROUP BY clause fields meet the current query record's values for the same fields. We use a SELECT DISTINCT statement since we don't want to include records that have the same field values across multiple records.

Using the SQL statement, we create a DAO recordset. Then we loop through the recordset, creating a string by adding the value for our "concatenated field" for every record in our DAO recordset. The final result is the value of that is passed to the function, which will then appear in the query.

There are some conditions that need to be met for this to work.

First, the "Concatenated Field", and all the fields in the GROUP BY clause must all be in the same data source, or perhaps record source is the better term. That is to say, they must all come from the same table or query. If you are trying to use this from a query that is joining multiple tables and using fields in the GROUP BY clause, then you will have to call the function from another query and set the data source to the first query. So you may end up with one query that that summarizes data by the GROUP BY clause, one that shows ALL the detail, and one that concatenates the field. And then you may have to join the first summary query with the query that performs that concatenation.

So I had the idea to allow an SQL string, instead of the name of a table or query, to be passed as the strDataSource argument. My guess is that parts of the SQL string would be "filled in" by values from the query's records. I don't know under what circumstances this would be useful but since it was a minor addition to the code, I added it.

As is often the case, it's a lot easier to understand what I have done by stepping through the VBA code than to try and understand a written explanation. So, download the sample file (see links section) and look through it. If you come up with a more elegant method or another use for the function, please let me know. I'd love to see what other people have done.

[Note: A version of this article was previously posted on a website that I used to maintain but I no longer own that domain. And I had named the function fConcatenateFldGroupBy(); what was I thinking?

UPDATED VERSION

I've updated the code to allow the passing of a single WHERE SQL clause string for aFldVal for those times where the criteria doesn't fit a GROUP BY clause when the grouping fields use only an 'equal to' comparison. There may be times you need to use less than (<) or more than (>). This occurred to me after writing my article on running sums and thinking more about how the built-in domain aggregate functions work. So this can now behave like the built-in domain aggregate functions.

I also added the ability to specify a string to use as the delimiter.

By default DConcat() sorts the concatenated strings in ascending order. Allen Browne's function allows you to add an ORDER BY string as an argument. DConcat can do the same, but you'll have to supply the WHERE and ORDER BY SQL string, instead of using the aFldVal paramarray argument. I've updated the sample file to show how. I've also added Allen Browne's function to show you how both function can produce the same results.

VBA Code

Option Compare Database
Option Explicit


Public Function DConcat(strDataSource As String, _
                        strConcatenateField As String, _
                        strDelimiter As String, _
                        ParamArray aFldVal() As Variant) _
       As String
    '*************************************************************************
    'DConcat()
    'Written by Azli Hassan, http://azlihassan.com/apps
    '© Azli Hassan, http://azlihassan.com/apps
    '
    'Updated (5/6/2018): Can now pass a single WHERE string to aFldVal
    '                    as you would with regular domain aggregate functions.
    'Updated (5/26/2018): Added option to specify string to use as delimiter
    '
    'PURPOSE:   To concatenate all the values of a field in a
    '           table or query that meets the grouping of the
    '           calling query
    '
    'ARGUMENTS:
    ' 1) strDataSource [String]
    '    - Name of table/query that field to be concatenated is in
    '    - May also be an SQL string to be used to set a recordset.
    ' 2) strConcatenateField [String]
    '    - Name of field to be concatenated.
    ' 2) strDelimiter [String]
    '    - String to use as delimiter (seperator) between value.
    ' 4) aFldVal() [Array]
    '    - An array of GroupBy fields and their values.
    '      Must be pass from the query in a repeating order of
    '      Field name (as a string), then the Field value, and so on
    '      By default, concatenated values are ordered ascendingly.
    '      If you need a particular sort order then you'll need to
    '      pass a single WHERE and ORDER BY SQL statement to aFldVal().
    '
    'RETURNS: Concatenated string of UNIQUE values of concatenated string
    '         where data sources fields match the calling queries groupings
    '
    'TIP: Remove or Comments out the Debug.Print statements
    '     AFTER you understand how the function works.
    '*************************************************************************

    On Error GoTo ErrMsg:

    Dim Db As DAO.Database, _
        rst As DAO.Recordset, _
        fldConcatenate As DAO.Field
    Dim strParamArray As String, _
        lngNumOfElements As Long, _
        blnIsNumeric As Boolean
    Dim strSql As String, _
        strSELECT As String, _
        strFROM As String, _
        strWhere As String, _
        strCRITERIA As String
    Dim blnText As Boolean
    Dim strAdd As String

    'Check that table/query exists in current database
    'IsTableQuery() - http://support.microsoft.com/kb/210398/
    If Not IsTableQuery("", strDataSource) Then
        Dim rstTemp As DAO.Recordset
        Set rstTemp = CurrentDb.OpenRecordset(strDataSource)
        If rstTemp.BOF And rstTemp.EOF Then GoTo ExitHere
        rstTemp.Close
        strFROM = "FROM (" & Left(strDataSource, Len(strDataSource) - 1) & _
                  ") as myDataSource "
    Else
        strFROM = "FROM " & strDataSource & " "
    End If

    Set Db = CurrentDb()
    Set rst = Db.OpenRecordset(strDataSource)

    'Check that table/query has data
    If rst.BOF And rst.EOF Then GoTo ExitHere

    'Check if parramarray is empty
    If IsEmpty(aFldVal) Then
        DConcat = "#ERR-EmptyParramarray"
    End If
    
    'Check if only 1 thing was passed to parramarray.
    'If so, then assume the whole WHERE string was passed.
    If LBound(aFldVal) = UBound(aFldVal) Then
        'Only 1 element was passed
        strWhere = "WHERE "
        strWhere = strWhere & CStr(aFldVal(LBound(aFldVal)))
        strWhere = strWhere & ";"
    Else
        'More than 1 thing passed
        'Get number of elements in parramarray
        If LBound(aFldVal) = 0 Then
            lngNumOfElements = UBound(aFldVal) + 1
        Else
            lngNumOfElements = UBound(aFldVal) + 1
        End If
        'Check that paramarray has even number of elements
        If lngNumOfElements Mod 2 <> 0 Then Exit Function
        Dim i As Long
        For i = LBound(aFldVal) To UBound(aFldVal) Step 2
            blnIsNumeric = IsNumeric(aFldVal(i + 1))
            Select Case blnIsNumeric
            Case True
                strParamArray = strParamArray & "'" & aFldVal(i) & _
                                "', " & aFldVal(i + 1) & ", "
            Case False
                If IsDate(aFldVal(i + 1)) Then
                strParamArray = strParamArray & "'" & aFldVal(i) & _
                                "', #" & aFldVal(i + 1) & "#, "
                Else
                strParamArray = strParamArray & "'" & aFldVal(i) & _
                                "', '" & aFldVal(i + 1) & "', "
                End If
            End Select
        Next i
        strParamArray = Left(strParamArray, _
                             Len(strParamArray) - Len(", "))
    
        Debug.Print "DConcat('" & strDataSource & _
                    "', '" & strConcatenateField & "', " & _
                    strParamArray & ")"
    
        For i = LBound(aFldVal) To (UBound(aFldVal)) Step 2
            blnText = (rst.Fields(aFldVal(i)).Type = dbChar) Or _
                      (rst.Fields(aFldVal(i)).Type = dbMemo) Or _
                      (rst.Fields(aFldVal(i)).Type = dbText)
            Select Case blnText
            Case True
                strCRITERIA = "[" & aFldVal(i) & "] = '" & _
                              aFldVal(i + 1) & "'"
            Case False
                If rst.Fields(aFldVal(i)).Type = dbDate Then
                    strCRITERIA = "[" & aFldVal(i) & "] = " & _
                                  "#" & aFldVal(i + 1) & "#"
                Else
                    strCRITERIA = "[" & aFldVal(i) & "] = " & _
                                  aFldVal(i + 1)
                End If
            End Select
            strWhere = strWhere & strCRITERIA & " AND "
        Next i
        strWhere = "WHERE (" & strWhere
        strWhere = Left(strWhere, Len(strWhere) - Len(" AND "))
        strWhere = strWhere & ");"
    End If
    
    
    'Create SQL String to select distinct records
    'that match the query's "GroupBy" values
    'e.g. SELECT DISTINCT Reference
    '     FROM tblData
    '     WHERE ((ProductID=2211) AND (Description="10�F 15V"));

    strSELECT = "SELECT DISTINCT " & strConcatenateField & " "
    
    strSql = strSELECT & strFROM & strWhere
    Debug.Print strSql

    Set rst = Db.OpenRecordset(strSql)

    'Check that SQL recordset has data
    If rst.BOF And rst.EOF Then GoTo ExitHere
    rst.MoveFirst

    'Set recordset field Object
    Set fldConcatenate = rst.Fields(strConcatenateField)

    'Loop through ALL the records
    'in the SELECT DISTICT recordset
    While Not rst.EOF
        With rst
            If DConcat = "" Then
                'First value
                If Not IsNull(fldConcatenate) Then
                    DConcat = fldConcatenate
                End If
            Else
                If Not IsNull(fldConcatenate) Then
                    strAdd = strDelimiter & fldConcatenate
                    If InStr(1, DConcat, _
                             strAdd, vbTextCompare) = 0 Then
                        'Only add if unique
                        DConcat = DConcat & strAdd
                    End If
                End If
            End If
        End With
        rst.MoveNext
    Wend

ExitHere:
    On Error Resume Next
    rstTemp.Close
    rst.Close
    Db.Close
    Exit Function

ErrMsg:
    DConcat = "#ERR" & Err.Number
    Debug.Print "Err.Number = " & Err.Number & _
                ", Err.Description = " & Err.Description
    Resume ExitHere

End Function

Links