Using Excel Date Functions in Access 2007

This content is outdated and is no longer being maintained. It is provided as a courtesy for individuals who are still using these technologies. This page may contain URLs that were valid when originally published, but now link to sites or pages that no longer exist.

**Summary: **Learn how to use Visual Basic for Applications (VBA) and Automation to take advantage of Microsoft Office Excel 2007 functions directly from your Microsoft Office Access 2007 application. (13 printed pages)

Sal Ricciardi, Microsoft Corporation

April 2009

**Applies to: **Microsoft Office Access 2007, Office Excel 2007

Contents

  • Introduction to Using Excel Functions in Your Access 2007 Application

  • Using Automation

  • Setting a Reference to Excel

  • Creating the Excel Object

  • Understanding the Basics of Calling Excel Functions

  • Ensuring That Your Startup Code Runs

  • Sending a Range to Excel

  • About the NetworkDays Function

  • About the EDate Function

  • About the EoMonth Function

  • About the WorkDay Function

  • Creating the Functions

  • Using Excel Functions in an Access Query

  • Using Excel Functions in an Access Form or Report

  • Closing Excel

  • Download the Sample Database

  • Additional Resources

Introduction to Using Excel Functions in Your Access 2007 Application

Microsoft Office Excel 2007 includes a library of built-in functions, many of which are not included in Microsoft Office Access 2007, but that you can still use. This article describes how to use Visual Basic for Applications (VBA) and Automation to use the Excel functions directly in your Microsoft Office Access 2007 application.

The article includes a sample database that shows how to call the Excel functions listed in the following table.

Table 1. Excel functions that are used in this article

Function

Description

NetworkDays

Calculates the number of working days between two given dates.

EDate

Adds or subtracts months from a given date.

EoMonth

Computes the last date in a given month.

WorkDay

Returns a work day from a past date or a future date.

Using Automation

Automation is the ability of one application to create and control the objects of another application and is a central component of the Microsoft Office Component Object Model (COM). Using Automation, you can use Access to create and control objects in Excel. To use Automation, first reference the application that contains the objects that you want to manipulate; in this case, the Excel functions that you want to use. Establishing that reference is not the only way to use them. However, it is recommended for the following reasons:

  • Establishing a reference provides design-time features that would not otherwise be available. For example, it provides information about the objects in the application; in this case, the objects in Excel. That information can prove valuable as you view objects from Excel in the Object Browser and write code in the VBA editor with help from IntelliSense.

  • Establishing a reference helps your code run faster because it provides VBA the information required to resolve calls to objects at compile time instead of at runtime. Because there is less work to do at runtime, the application runs faster.

  • Establishing a reference gives VBA the information required to perform type checking, which means that you can more immediately and accurately identify errors.

For more information about Automation and how to use Automation without using a reference, see Office Application Automation.

Setting a Reference to Excel

To set a reference to Excel, you must set a reference to the type library in Excel by using the follow steps.

To set a reference to Excel

  1. Open the Access database within which you want to use the Excel functions.

  2. On the Ribbon, click Database Tools.

  3. In the Macro tab, click Visual Basic. The Visual Basic Editor appears.

  4. In the Visual Basic Editor, click Tools, References.

  5. In the References dialog box, scroll to the Microsoft Excel 12.0 Object Library reference and verify that it is selected.

  6. Click OK.

Figure 1. References dialog box

References dialog box

Creating the Excel Object

After you set the reference to the Excel type library, you can create an Excel object. To create that object, first declare an object variable that you can use to reference the object. Use the Public, Private, Friend, or Dim statement with the appropriate programmatic identifier to declare the object variable. In this case, the programmatic identifier is Excel.Application for Excel. The following statement declares a public variable named xlApp to be a reference to an Excel application.

Public xlApp As Excel.Application

Notice that the statement does not create the object. It only creates the variable that references the object. To create the object, use the Set statement with the New keyword and the appropriate programmatic identifier.

Set xlApp = New Excel.Application

The Set statement opens an instance of Excel in the background and places a reference to that instance in the object variable so that you can use the object variable to access the objects, properties, and methods in Excel, and to call Excel functions.

NoteNote

For a list of supported 2007 Microsoft Office system programmatic identifiers, see OLE Programmatic Identifiers.

Understanding the Basics of Calling Excel Functions

After you have an object variable that references the Excel object, you can call Excel functions. For example, the EDate function in Excel returns a serial number that represents a date some number of months before or after a given date. The EDate function requires two values—a date and a number, and it returns a number. All three of these values are of the Variant data type. After you have the xlApp object variable defined, you can call EDate in Access using code.

Dim varSerial As Variant
varSerial = xlApp.EDate(#1/31/2009#, 1)

Because the EDate function returns a serial number that represents a date, the varSerial variable contains the value 39872 after this code runs.

To convert the serial number to a date, use the Access Cdate function.

Running Code at Startup

Every time that you use the Set statement with the New keyword to create an Excel object in Access, you open a new instance of Excel in the background. Because multiple open instances of Excel consume system resources, consider opening a single, global instance of Excel when your Access database starts. Keep that single copy open until you no longer need it, and then close Excel to free the resources.

You can create an AutoExec macro in Access that runs automatically when you open a database. The recommended strategy is to create a Startup user-defined function and then an AutoExec macro that calls that function.

To create the AutoExec macro

  1. On the Create tab, in the Other group, click Macro. If it is unavailable, click the arrow under the Module or the Class Module button, and then click Macro.

  2. In the Macro builder, in the first empty Action cell, select RunCode. Then, under Action Arguments, next to Function Name, type Startup ().

  3. Click the Microsoft Office Button, and then click Save As.

  4. In the Save As dialog box, under Macro Name, type AutoExec.

  5. Click OK and then close the Macro Builder.

Access will run the AutoExec macro automatically when you open the database. The AutoExec macro, in turn, runs the user-defined Startup function.

Ensuring That Your Startup Code Runs

Access enables a user to bypass the AutoExec macro by pressing and holding the SHIFT key at startup. To ensure that users do not skip the AutoExec macro, you can disable the AutoExec macro bypass by creating a special customer database property named AllowBypassKey. Access verifies the property at startup. If the property is set to False, Access disables the AutoExec macro bypass.

To create the AllowBypassKey property and change its state, use the ChangeProperty function, in the sample database, together with the following code example.

   Dim bResult As Boolean
   ' Set the AllowBypassProperty to False.
    Const DB_Boolean As Long = 1
    bResult = ChangeProperty("AllowBypassKey", _
        DB_Boolean, False)

When you run this code the first time, it creates the AllowBypassKey property. (You must close and reopen the database for it to take effect.)

The following code example is the ChangeProperty function from the sample database.

Function ChangeProperty(strPropName As String, _
    varPropType As Variant, _
    varPropValue As Variant) As Boolean
    ' Change an existing user defined property.
    ' If the property is not found, it is
    ' created.
    Dim dbs As Object
    Dim prp As Variant
    Const conPropNotFoundError = 3270

    Set dbs = CurrentDb
    On Error GoTo ChangeProperty_Error
    dbs.Properties(strPropName) = varPropValue
    ChangeProperty = True

ChangeProperty_Exit:
    Exit Function

ChangeProperty_Error:
    ' If Property not found, add it.
    If Err = conPropNotFoundError Then
        Set prp = dbs.CreateProperty(Name:=strPropName, _
            Type:=varPropType, _
            Value:=varPropValue)
        dbs.Properties.Append prp
        Resume Next
    Else
        ' Unknown error.
        ChangeProperty = False
        Resume ChangeProperty_Exit
    End If
End Function

What to Include in the Startup Function

The Startup function that you create should only contain code that has to run one time when the database is opened. For example, code to create the running instance of Excel and the object variable that references it. The Startup function is also a good place to create global variables or arrays, and verify that AllowBypassProperty is set to False. The following code example is the Startup function from the sample database.

' Declare object variable to refer to the Excel Application.
Public xlApp As Excel.Application

' Declare a variant to hold the array of holidays.
Public varHolidays As Variant

Public Function Startup()
    ' Public Function Startup() - Code to run when the database is
    ' initially opened.
    On Error GoTo Startup_Error
    Dim nHolidays As Integer
    Dim bResult As Boolean

    ' Set the AllowBypassProperty to False.
    Const DB_Boolean As Long = 1
    bResult = ChangeProperty("AllowBypassKey", _
        DB_Boolean, False)

    ' Create object reference to Excel.
    Set xlApp = New Excel.Application

    ' Create the Holidays array required by NetworkDays.
    nHolidays = CreateHolidaysArray(varArray:=varHolidays, _
        strHolidaysTable:="Holidays")
    Debug.Print nHolidays & " holidays."

Startup_Exit:
    Exit Function

Startup_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "Startup"
    GoTo Startup_Exit

    End Function

The Startup function first establishes an error handler. Then the function sets the AllowBypassKey property to False to ensure that users cannot bypass the AutoExec macro. Next, the Set statement opens Excel and establishes xlApp as the reference object. Because xlApp is declared as Public, it is available to all procedures and can be used in all procedures to evaluate Excel functions.

The Startup function ends with a call to the CreateHolidaysArray function, that is explained in the next section.

Sending a Range to Excel

Some of the functions in Excel require a Range parameter. To meet the requirement, developers often create an Excel worksheet object, copy data into that worksheet, and then create an Excel Range object to pass to the function. Depending on your task, that is an acceptable approach. However, one alternative is to place the data in an array and send the array instead. The array is automatically converted to the range of values expected by the function. If your data requirements are small and you do not otherwise need a worksheet object, an array is often faster.

Two of the Excel functions in this article expect a range of holidays as a parameter. Because it is common to store holidays in an Access table, the CreateHolidaysArray user-defined function called in the Startup function loops through a table of holidays and creates the array.

Public Function CreateHolidaysArray(ByRef varArray As Variant, _
    ByRef strHolidaysTable As String)
    ' Create the varArray array to hold the date
    ' values from the Holiday column in the
    ' strHolidaysTable table.
    On Error GoTo CreateHolidaysArray_Error
    Dim dbs As DAO.Database
    Dim rst As DAO.Recordset
    Dim intRecs As Integer
    intRecs = 0
    
    ' Set object reference to the current database and open a
    ' recordset on the holidays table.
    Set dbs = CurrentDb()
    Set rst = dbs.OpenRecordset(strHolidaysTable, _
        dbOpenDynaset, dbReadOnly)
    
    If rst.AbsolutePosition > -1 Then
        rst.MoveLast
    Else
        ' No holidays!
        intRecs = 0
        GoTo CreateHolidaysArray_Close
    End If
    
    ' Construct the holidays array that is needed by functions
    ' like NetworkDays.
    ReDim varArray(rst.RecordCount)
    If rst.RecordCount <> 0 Then rst.MoveFirst
    Do While Not rst.EOF
        intRecs = intRecs + 1
        varArray(intRecs) = rst("Holiday").Value
        rst.MoveNext
    Loop
    
    ' Set the return value.
    CreateHolidaysArray = intRecs
    
    ' Close the recordset and release the object reference.
CreateHolidaysArray_Close:
    rst.Close
    Set rst = Nothing
       
CreateHolidaysArray_Exit:
    Exit Function

CreateHolidaysArray_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "CreateHolidaysArray"
    GoTo CreateHolidaysArray_Exit
    End Function

About the NetworkDays Function

The NetworkDays function in Excel calculates the number of working days between two dates, excluding weekdays and holidays. You pass the function a start date, an end date, and a range of date values (holidays) to exclude, and it returns the number of working days.

NoteNote

For more information about how to calculate the number of working days in Access without using Excel, see Counting the Number of Working Days in Access 2007.

The Workdays user-defined function in the code example implements a call to the NetworkDays function from Access. Workdays strips the time component from the arguments that are passed and then verifies that the start date is earlier than the end date. If the start date is not earlier than the end date, the two are swapped. Workdays uses the xlApp object variable that you created in the Startup function to manage the request to Excel to call NetworkDays. In addition, the varHolidays array created in the Startup function provides the list of holidays to exclude.

Public Function Workdays(ByRef startDate As Date, _
    ByRef EndDate As Date) As Double
    ' Returns the number of workdays between startDate
    ' and endDate inclusive.  Workdays excludes weekends, and
    ' excludes the holidays, if any, in the varHolidays array.
    ' Uses the NetworkDays function in Excel.
    On Error GoTo Workdays_Error
    Dim dtmX As Date

    ' DateValue returns the date part only.
    startDate = DateValue(startDate)
    EndDate = DateValue(EndDate)
    
    ' If the end date is earlier, swap the dates.
    If EndDate < startDate Then
        dtmX = startDate
        startDate = EndDate
        EndDate = dtmX
    End If
    
    ' Call Excel function.
    Workdays = xlApp.NetworkDays(startDate, EndDate, varHolidays)
    
Workdays_Exit:
    Exit Function

Workdays_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "Workdays"
    GoTo Workdays_Exit
    
    End Function
NoteNote

The Excel functions discussed in this article are included as part of Excel 2007. However, in earlier versions of Excel, they were part of the separately installed Analysis Toolpak add-in.

About the EDate Function

The EDate function calculates a date that is some number of months going forward or backward from a given start date. You can use it to calculate due dates that occur on the same date each month. You can use the AddMonths user-defined function in the code example to wrap a call to EDate from Access. One advantage to wrapping the function in this manner is that you can call the AddMonths function from an Access Query.

Public Function AddMonths(ByRef startDate As Date, _
    ByRef numberOfMonths As Integer) As Variant
    ' Returns the serial number of the date that is
    ' numberOfMonths from the startDate, using the Excel
    ' EDate function.
    On Error GoTo AddMonths_Error

    ' Call Excel function.
    AddMonths = xlApp.EDate(startDate, numberOfMonths)

AddMonths_Exit:
    Exit Function

AddMonths_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "AddMonths"
    GoTo AddMonths_Exit
    
    End Function

About the EoMonth Function

The EoMonth function in Excel calculates the last day of the month some number of months in the future or in the past. You can use it to calculate a due date that occurs on the last day of the month. The EndOfMonth user-defined function code example calls the EoMonth function from Access.

Public Function EndOfMonth(ByRef startDate As Date, _
    ByRef numberOfMonths As Integer) As Variant
    ' Returns the serial number of the date that is
    ' the end of the month numberOfMonths from
    ' the startDate, using the Excel
    ' EoMonth function.
    On Error GoTo EndOfMonth_Error

    ' Call Excel function.
    EndOfMonth = xlApp.EoMonth(startDate, numberOfMonths)

EndOfMonth_Exit:
    Exit Function

EndOfMonth_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "EndOfMonth"
    GoTo EndOfMonth_Exit

    End Function

About the WorkDay Function

The WorkDay function in Excel can be used to add or subtract workdays from a given start date (weekends and holidays are not counted). For example, you might want to calculate the end date for a project that requires ten working days. In the Workday user-defined function code example, you provide the start date and the number of days and the function automatically uses the varHolidays array to provide the list of holidays to the Excel WorkDay function.

Public Function Workday(ByRef startDate As Date, _
    ByRef numberOfDays As Integer) As Variant
    ' Returns the serial number of the date that is
    ' the workday that is numberOfDays from the startDate.
    ' Excludes weekend days, and excludes holidays, if any,
    ' that exist in the varHolidays array.
    ' Uses the Excel WorkDay function.
    On Error GoTo Workday_Error

    ' Call Excel function.
    Workday = xlApp.Workday(startDate, numberOfDays, varHolidays)

Workday_Exit:
    Exit Function

Workday_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "Workday"
    GoTo Workday_Exit
    End Function

Creating the Functions

The sample database for this article contains the functions shown in the code examples. After you download the sample database, open the ExcelInAccess code module to retrieve the functions. To create the functions in this article, start Access and follow these steps.

NoteNote

These instructions apply to Microsoft Office Access 2007. If you have a different version, the steps may vary.

To create the functions in this article

  1. Start Microsoft Access.

  2. Click the Microsoft Office Button, click Open, and then open the database where you want to insert the functions.

  3. On the Ribbon, click Database Tools.

  4. On the Macro tab, click Visual Basic.

  5. On the Insert menu, click Module.

  6. At the top of the module, if they are not already there, type the following two lines:

    Option Compare Database

    Option Explicit

    Or, if you downloaded the sample database, copy and paste the functions from the code module.

  7. On the File menu, click Save.

  8. Type a module name, such as ExcelInAccess, and then press ENTER.

  9. On the Debug menu, click Compile.

  10. On the File menu, click Close and Return to Microsoft Office Access.

After you place the functions in your database, you can use them in Access objects such as queries, forms, and reports.

Using Excel Functions in an Access Query

You cannot access an Excel function directly from an Access query. Instead, you must write a VBA user-defined function, and make the call to Excel in that function. You can then call the VBA user-defined function from a query.

This article discusses four Excel functions and their corresponding VBA user-defined functions.

Table 2. Excel functions and the corresponding VBA wrapper functions

Excel function

User-defined wrapper function

NetworkDays

Workdays(startdate, enddate)

EDate

AddMonths(startdate, months)

EoMonth

EndOfMonth(startdate, months)

WorkDay

Workday(startdate, days)

To create a query column for the results that a user-defined function returns, you add an expression to the query grid, and in that expression, call the user-defined function. For example, to add the NetworkDays calculation, you place the following expression in the Fields cell of a new column in the Query grid.

NetworkDays: Workdays([startdate],[enddate])

This expression instructs Access that you want the title of the column to be NetworkDays. The expression also specifies that you want this column to contain the evaluation result from the Workdays function, with startdate and enddate passed as the arguments. When Access processes the query, it evaluates the expression for every row in the query result.

As another example, suppose that you want to create a column for the results of test calls to the EDate function. To create that column, place the following expression in the Fields cell of a new column in the Query grid.

EDate: AddMonths([startdate], 1)

This expression gives the column the title EDate. It also specifies that you want the column to contain the evaluation result from the AddMonths function, with startdate and 1 passed as the arguments. Because AddMonths returns a serial number, the code will generate a column of numbers. To convert the numbers to dates, use the following code.

EDate: CDATE(AddMonths([startdate], 1))

This code wraps the call to the wrapper function inside a call to Cdate, which means "Convert to Date".

The Excel Functions Query in the sample database shows how to use the four wrapper functions in an Access query.

Figure 2. Using the four wrapper functions in an Access query

Using the wrapper functions in an Access query

Using Excel Functions in an Access Form or Report

To call an Excel function in an Access form or report, begin by placing a text box control on the design surface of your form or report. To add the EoMonth calculation to compute a due date, add an expression to the Control Source property of your text box. The Control Source property indicates to Access where it can get the data for the control. To place the calculation in the text box, insert the following expression in the Control Source property of the text box.

=CDATE(EndOfMonth([startdate],1))

The equal sign (=) is important because it instructs Access that what follows is an expression instead of a field name. This expression converts the serial number from the EndOfMonth function to a date and displays it in the text box.

When you create your form or report, verify that the Record Source property contains the name of a table or query that includes the fields that you want to reference. In this case, the EndOfMonth function requires the startDate field. Therefore, it must be present in the underlying table or query.

Closing Excel

After you finish calling Excel functions and no longer have to communicate with Excel, call the Quit method to close the open instance of Excel. You can then use the Set statement to reset the object reference and to release memory and resources.

The sample database uses the Shutdown user-defined function in the code example to perform these tasks. You could call this function from your main form when the user clicks the Exit button.

Public Function Shutdown()
    ' Run this function at shutdown to close
    ' Excel and release any memory.
    On Error GoTo Shutdown_Error

    ' Quit Excel.
    xlApp.Quit

    ' Reset object reference and release memory.
    Set xlApp = Nothing

Shutdown_Exit:
    Exit Function

Shutdown_Error:
    MsgBox "Error " & Err.Number & ": " & Err.Description, _
        vbCritical, "Shutdown"
    GoTo Shutdown_Exit
    End Function

Download the Sample Database

You can download the Excel Functions Sample Database for Access 2007 that contains the module mentioned in this article.

Additional Resources

For more information, see the following resources: