Callback functions in Microsoft Access VBA. Part 1

Gustav BrockMVP
CERTIFIED EXPERT
Published:
Callback functions are a hidden gem in Microsoft Access. With these, you can dynamically fill a combobox or listbox entirely from code with a versatility way beyond what a simple static value list can offer. To get started, learn the basics.

Little known feature of Microsoft Access

Callback functions can be a little hard to get a hold of but, once you master the technique, they can meet just about any need, no matter how complex.

This series of three articles will cover:

  1. The basics of callback functions
  2. Making the callback function configurable
  3. Sharing one callback function between several controls

This is the first article. Links to the second and the third articles can be found at the bottom of this article.


Get started

For a start, browse the official documentation which is hard to locate if you don't have the magic keywords:

ComboBox.RowSourceType property (Access)
ListBox.RowSourceType property (Access)

The information on these pages about this topic is, however, obtuse:
You can also set the RowSourceType property with a user-defined function. The function name is entered without a preceding equal sign (=) and without the trailing pair of parentheses. You must provide specific function code arguments to tell Access how to fill the control.
However, they both contain a link to a page with useful information:

RowSourceType property (user-defined function) code argument values

This page explains the syntax and provides two examples that can serve as skeletons for your own functions. Study this carefully to get a hold of the very special way these functions operate and are called.

Access both calls such a function multiple times and gets values back, thus they are nicknamed callback functions, even though callback in all other programming languages means something very different.

Each call comes with a value for the parameter Code that via the Select Case block controls what task the function shall carry out for this call. The main tasks are:
When the form opens:

  • Initialise the function
  • Set up rows and columns
  • Fill rows

When the form closes:

  • Option to clean up


Example 1

Take the first example from that page, the function that lists the next four Mondays:

Public Function ListMondays( _
    ByRef ctl As Control, _
    ByVal Id As Long, _
    ByVal Row As Long,
    Byval Column As Long,
    Byval Code As Integer) _
    As Variant

    Dim Offset      As Integer
    Dim WeekdayDate As Date

    Select Case Code
        Case acLBInitialize     ' Initialize.
            ListMondays = True
        Case acLBOpen           ' Open.
            ListMondays = Timer ' Unique ID.
        Case acLBGetRowCount    ' Get rows.
            ListMondays = 4
        Case acLBGetColumnCount ' Get columns.
            ListMondays = 1
        Case acLBGetColumnWidth ' Get column width.
            ListMondays = -1    ' Use default width.
        Case acLBGetValue       ' Get the data.
            Offset = Abs((9 - Weekday(Date)) Mod 7) 
            WeekdayDate = DateAdd("d", Offset + 7 * row, Date) 
            ListMondays = Format(WeekdayDate, "mmmm d")     
        End Select

End Function

For the first calls, it sets up the column and row counts and the column width. Then, reaching Case acLBGetValue it calculates the upcoming Monday and the three subsequent Mondays and formats these for a human friendly display like:

Monday
June 14
June 21
June 28
July 5

While this makes it easy for the user to select the right Monday and, say, June 21 is what you wish to insert in an e-mail message, it isn't of much use if its the date of that Monday you want.

Another limitation of this example is, that the function name is used for returning values. Thus, if you wish to modify the name of the function, no less than seven places must the code be adjusted.

Improved example

Another example will show how to eliminate these limitations and introduce a few refinements. This example will list the names of the weekdays of a week and the VBA weekday value of these:

' Callback function to list the weekday names of a week.
' The selected value will be a value of enum VbDayOfWeek (Long).
' The displayed values will be those of WeekdayName(DayOfWeek, False, vbSunday).
'
' Example for retrieval of selected value:
'
'   Dim DayOfWeek As VbDayOfWeek
'   DayOfWeek = Me!ControlName.Value
'
' Typical settings for combobox or listbox:
'
'   ControlSource:  Bound or unbound
'   RowSource:      Leave empty
'   RowSourceType:  CallWeekdays
'   BoundColumn:    1
'   LimitToList:    Yes
'   AllowEditing:   No
'   Format:         None
'   ColumnCount:    Don't care. Will be set by the function
'   ColumnWidths:   Don't care. Will be overridden by the function
'
' 2021-02-19. Cactus Data ApS, CPH.
'
Public Function CallWeekdays( _
    ByRef Control As Control, _
    ByVal Id As Long, _
    ByVal Row As Long, _
    ByVal Column As Variant, _
    ByVal Code As Integer) _
    As Variant

    ' Adjustable constants.
    '
    ' Left margin of combobox to align the values on list with the formatted value displayed.
    ' Empiric value.
    Const LeftMargin        As Integer = 23

    ' Fixed constants.
    '
    ' Count of rows to display.
    Const RowCount          As Long = DaysPerWeek
    ' Count of columns in the control.
    Const ColumnCount       As Long = 2

    Static ColumnWidth(0 To ColumnCount - 1) As Integer
    Static FirstDayOfWeek   As VbDayOfWeek

    Dim DayOfWeek           As VbDayOfWeek
    Dim Value               As Variant

    Select Case Code
        Case acLBInitialize
            ' Control settings.
            Control.ColumnCount = ColumnCount   ' Set the colum count of the control.
            ColumnWidth(0) = HiddenColumnWidth  ' Hide the bound (value) column.
            ColumnWidth(1) = DefaultColumnWidth ' Set the width of the display column to the default width.
            If Control.ControlType = acComboBox Then
                Control.LeftMargin = LeftMargin ' Adjust left margin of combobox.
            End If

            ' Value settings.
            FirstDayOfWeek = SystemDayOfWeek    ' First day in the week as to the system settings.

            ' Initialize.
            Value = True                        ' True to initialize.
        Case acLBOpen
            Value = Timer                       ' Autogenerated unique ID.
        Case acLBGetRowCount                    ' Get count of rows.
            Value = RowCount                    ' Set count of rows.
        Case acLBGetColumnCount                 ' Get count of columns.
            Value = ColumnCount                 ' Set count of columns.
        Case acLBGetColumnWidth                 ' Get the column width.
            Value = ColumnWidth(Column)         ' Use preset column widths.
        Case acLBGetValue                       ' Get the data for each row.
            DayOfWeek = (FirstDayOfWeek + Row - 1) Mod DaysPerWeek + 1
            If Column = 0 Then
                ' Return weekday value.
                Value = DayOfWeek
            Else
                ' Return friendly name for display.
                Value = StrConv(WeekdayName(DayOfWeek, False, vbSunday), vbProperCase)
            End If
        Case acLBGetFormat                      ' Format the data.
            ' N/A                               ' Apply the value or the display format.
        Case acLBClose                          ' Do something when the form recalculates or closes.
            ' no-op.
        Case acLBEnd                            ' Do something more when the form recalculates or closes.
            ' no-op.
    End Select

    ' Return Value.
    CallWeekdays = Value

End Function

First, it uses constants throughout to avoid “magic numbers” and to ease customisation. Next, it operates with two columns, where the first (the “data column”) is the weekday value, and the second is the formatted text to display for the user. ColumnWidth is an array holding the column widths of the columns of which the first is zero, thus hidden, as the value from this is for the code of the form only, not for display. The array is static, so its values only need to be specified once.

The setting of the left margin is cosmetic only; it aligns the value displayed in the combobox with the values displayed in the dropdown list for a neater visual appearance of the combobox control during the interaction with the user, when he/she browses the items to make a selection.

You will notice another static variable, FirstDayOfWeek. These hold their values between the multiple calls of the function and need only to be set once - at the initial call of the function, not for every call of the function, thus speeding up the subsequent calls. For this function, the speed gain isn't that much, but for similar functions, where data are retrieved from stored data, it can be dramatic.

Finally, the first weekday to display is found from the system settings of Windows by this function:

' Returns the weekday of the first day of the week according to the current Windows settings.
'
' 2017-05-03. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function SystemDayOfWeek() As VbDayOfWeek

    Const DateOfSaturday    As Date = #12:00:00 AM#

    Dim DayOfWeek   As VbDayOfWeek

    DayOfWeek = vbSunday + vbSaturday - Weekday(DateOfSaturday, vbUseSystemDayOfWeek)

    SystemDayOfWeek = DayOfWeek

End Function

Now the combobox can be filled by calculating the weekdays for the first column and, by the function WeekdayName, obtaining the friendly (localised) names of these for the second column. There is no format to apply, as the values for the visible column are text. The dropdown could look like this:

Returning date values

While returning integers and text from a callback function isn't difficult, it is another matter regarding date and time, as such values also must be applied a format to be displayed.
This, however, is easily solved using a callback function for the combobox or listbox, as it returns a Variant which can hold any data type including Date. This means that - by using two columns - you can let the first return a true Date value and the second (the visible) return a formatted value that fits the purpose of the combobox or listbox on the form.
An example is the following function, which simply lists the days (displayed as Monday, Tuesday, etc.) of the current week and - when a day is selected - returns the date of this as a date value:

' Callback function to list the weekday names of a week.
' The selected value will be the date of the weekday in the current week.
' The displayed values will be those of WeekdayName(DayOfWeek, False, vbSunday).
'
' Example for retrieval of selected value:
'
'   Dim DateOfWeek As Date
'   DateOfWeek = Me!ControlName.Value
'
' Typical settings for combobox or listbox:
'
'   ControlSource:  Bound or unbound
'   RowSource:      Leave empty
'   RowSourceType:  CallThisWeekDates
'   BoundColumn:    1
'   LimitToList:    Yes
'   AllowEditing:   No
'   Format:         None
'   ColumnCount:    Don't care. Will be set by the function
'   ColumnWidths:   Don't care. Will be overridden by the function
'
' 2021-02-16. Cactus Data ApS, CPH.
'
Public Function CallThisWeekDates( _
    ByRef Control As Control, _
    ByVal Id As Long, _
    ByVal Row As Long, _
    ByVal Column As Variant, _
    ByVal Code As Integer) _
    As Variant

    ' Adjustable constants.
    '
    ' Left margin of combobox to align the values on list with the formatted value displayed.
    ' Empiric value.
    Const LeftMargin        As Integer = 23

    ' Fixed constants.
    '
    ' Count of rows to display.
    Const RowCount          As Long = DaysPerWeek
    ' Count of columns in the control.
    Const ColumnCount       As Integer = 2

    Static ColumnWidth(0 To ColumnCount - 1) As Integer
    Static FirstDateOfWeek  As Date

    Dim DateOfWeek          As Date
    Dim Value               As Variant

    Select Case Code
        Case acLBInitialize
            ' Control settings.
            Control.ColumnCount = ColumnCount   ' Set the colum count of the control.
            ColumnWidth(0) = HiddenColumnWidth  ' Hide the bound (value) column.
            ColumnWidth(1) = DefaultColumnWidth ' Set the width of the display column to the default width.
            If Control.ControlType = acComboBox Then
                Control.LeftMargin = LeftMargin ' Adjust left margin of combobox.
            End If

            ' Value settings.
                                                ' First date of the week as to the system settings.
            FirstDateOfWeek = DateThisWeekPrimo(Date, vbUseSystemDayOfWeek)

            ' Initialize.
            Value = True                        ' True to initialize.
        Case acLBOpen
            Value = Timer                       ' Autogenerated unique ID.
        Case acLBGetRowCount                    ' Get count of rows.
            Value = RowCount                    ' Set count of rows.
        Case acLBGetColumnCount                 ' Get count of columns.
            Value = ColumnCount                 ' Set count of columns.
        Case acLBGetColumnWidth                 ' Get the column width.
            Value = ColumnWidth(Column)         ' Use preset column widths.
        Case acLBGetValue                       ' Get the data for each row.
            DateOfWeek = DateAdd("d", Row, FirstDateOfWeek)
            If Column = 0 Then
                ' Return date of weekday.
                Value = DateOfWeek
            Else
                ' Return friendly name for display.
                Value = StrConv(Format(DateOfWeek, "dddd"), vbProperCase)
            End If
        Case acLBGetFormat                      ' Format the data.
            ' N/A                               ' Apply the value or the display format.
        Case acLBClose                          ' Do something when the form recalculates or closes.
            ' no-op.
        Case acLBEnd                            ' Do something more when the form recalculates or closes.
            ' no-op.
    End Select

    ' Return Value.
    CallThisWeekDates = Value

End Function

This function will also return a fixed count of seven rows, but this time the returned value will be the date of the selected weekday.

When initialised, it will find the date for the first weekday of the current week according to the settings of Windows. It uses a supporting function for this, which will not be listed here, but essentially uses this expression:

FirstDateOfWeek = DateAdd("d", 1 - Weekday(Date, vbUseSystemDayOfWeek), Date)

The value is stored in the static variable FirstDateOfWeek and then, for each of the following days, one day is added to that date.

As for the format of the displayed days, this is fixed, and the resulting text - the names of the weekdays - is what will be listed.

Select weekday date in a form

To turn the function into practical use is quite simple:

  • create a combobox
  • adjust its settings

The settings to set are few and basic (see in-line comments at top) as the function controls some of the critical settings of the control.

The operation may also be simple. For example, to set the selected date for display in a textbox, use an AfterUpdate event like this:

Private Sub ThisWeekDates_AfterUpdate()

    Me!WeekdayDate.Value = Me!ThisWeekDates.Value

End Sub

Here is an example of such a form:


This form is included in the demo. Open it, select any weekday, and the date displayed will be of that weekday in the current week no matter which weekday is the first of the week.


Conclusion

It has been shown what steps are needed to create a basic as well as an improved callback function for Microsoft Access. If you miss features like reconfiguring a callback function, please proceed with the next articles in this series:

Callback functions in Microsoft Access VBA. Part 2
Callback functions in Microsoft Access VBA. Part 3

Code and download

The full code and demos are attached for Microsoft Access 365.

Microsoft Access: CallbackDemo.accdb

At any time, full and updated code is available on GitHub: VBA.Callback
I hope you found this article useful. You are encouraged to ask questions, report any bugs or make any other comments about it below.

Note: If you need further "Support" about this topic, please consider using the Ask a Question feature of Experts Exchange. I monitor questions asked and would be pleased to provide any additional support required in questions asked in this manner, along with other EE experts.

Please do not forget to press the "Thumbs Up" button if you think this article was helpful and valuable for EE members.


2
2,847 Views
Gustav BrockMVP
CERTIFIED EXPERT

Comments (1)

DatabaseMX (Joe Anderson - Former Microsoft Access MVP)Database Architect / Application Developer
CERTIFIED EXPERT
Top Expert 2007

Commented:
Most definitely useful Gustav.
Thanks for posting.
Joe

Have a question about something in this article? You can receive help directly from the article author. Sign up for a free trial to get started.