Access VBA Tables – Update, Count, Delete, Create, Rename, Export

Written by

Editorial Team

Reviewed by

Steve Rynearson

Last updated on July 9, 2022

This tutorial will teach you how to work with Access Tables using VBA.

Access VBA Tables

To start we will demonstrate the simple commands for working with Tables in Access. Later in this tutorial we will show you full professionally developed functions for working with tables in Access.

Create Table

This code will use SQL to create a table named “Table1” with fields “ID” and “Name”:


    Dim table_name As String
    Dim fields As String
    
    table_name = "Table1"
    fields = "([ID] varchar(150), [Name] varchar(150))"
    
    CurrentDb.Execute "CREATE TABLE " & table_name & fields

Close Table

This line of VBA code will close a Table (saving changes):

DoCmd.Close acTable, "Table1", acSaveYes

To close a Table without saving:

DoCmd.Close acTable, "Table1", acSaveNo

Delete Table

This code will delete a Table (note: first the Table should be closed):

DoCmd.Close acTable, "Table1", acSaveYes
DoCmd.DeleteObject acTable = acDefault, "Table1"

Rename Table:

This line of code will rename an Access Table:

DoCmd.Rename "Table1", acTable, "Table1_New"

Another option is using the TableDefs property of a database object.

Set tdf = db.TableDefs(strOldTableName)
tdf.Name = strNewTableName

Empty / Clear Table

This VBA code will empty a Table:

DoCmd.RunSQL "DELETE * FROM " & "Table1"

Truncate Table / Delete Records

This line of VBA code uses SQL to delete records from a table that meet certain criteria:

DoCmd.RunSQL ("DELETE * FROM " & "Table1" & " WHERE " & "num=2")

Export Table to Excel

To export a Table to Excel use the DoCmd.OutputTo method:

DoCmd.OutputTo acOutputTable, "Table1", acFormatXLS, "c:\temp\ExportedTable.xls"

or use the DoCmd.TransferSpreadsheet method:

DoCmd.TransferSpreadsheet acExport, acSpreadsheetTypeExcel9, "Table1", "c:\temp\ExportedTable.xls", True

Update Table

The following code will update a record, without displaying the warning message:

DoCmd.SetWarnings (False)
DoCmd.RunSQL "Update ProductsT SET ProductsT.ProductName = 'Product AAA' WHERE (((ProductsT.ProductID)=1))"

VBA Programming | Code Generator does work for you!

Access VBA Table Functions

The above code examples are the simple commands you can use to interact with Tables using VBA. However, you will often need to add much more supporting code (including error handling) to properly utilize these commands.  Below you will find professionally develop functions for working with Tables in Access.

Count Table Records

This function will count the number of records in a table:

Public Function Count_Table_Records(TableName As String) As Integer
On Error GoTo Err:

    Dim r As DAO.Recordset
    Dim c As Integer
    Set r = CurrentDb.OpenRecordset("Select count(*) as rcount from " & TableName).OpenRecordset
    
    If (r.EOF) Then
        c = 0
    Else
        c = Nz(r!rCount, 0)
    End If
   
    Count_Table_Records = c
    Exit Function

Err:
    Call MsgBox("An error occured: " & Err.Description, vbExclamation, "Error")
End Function

'Usage Example
Private Sub Count_Table_Records_Example()
   MsgBox (Count_Table_Records("Table1"))
End Sub

 

Check if Table Exists Function

This Function will test if a table exists, returning TRUE or FALSE:

Public Function TableExists(ByVal strTableName As String) As Boolean
    
    'Function: Determine if table exists in an Access database
    'Arguments:strTablename:   Name of table to check
    Dim tdf As DAO.TableDef
    
    On Error Resume Next
    Set tdf = CurrentDb.TableDefs(strTableName)
    TableExists = (Err.Number = 0)

End Function

Here is an example of the function in use:

Private Sub TableExists_Example()
    If VBA_Access_Checks.TableExists("Table") = True Then
        MsgBox ("Table was found!")
    Else
        MsgBox ("Table was NOT found!")
    End If
End Sub

Create Table Function

This function will create a Table in Access VBA in the Current Database:

Public Function CreateTable(table_fields As String, table_name As String) As Boolean
    Dim strCreateTable As String
    Dim intCount As Integer
    Dim strFields() As String
    Dim strValues() As String
    Dim strInsertSQL As String
    Dim intCounter As Integer
    Dim intData As Integer
 
    On Error GoTo Err
 
    strFields = Split(table_fields, ",")
 
 
    strCreateTable = "CREATE TABLE " & table_name & "("
 
    For intCounter = 0 To UBound(strFields) - 1
        strCreateTable = strCreateTable & "[" & strFields(intCounter) & "] varchar(150),"
    Next
 
    If Right(strCreateTable, 1) = "," Then
        strCreateTable = Left(strCreateTable, Len(strCreateTable) - 1)
        strCreateTable = strCreateTable & ")"
    End If
 
    CurrentDb.Execute strCreateTable
 
    intCounter = 0
    intData = 0
 
    If Err.Number = 0 Then
        CreateTable = True
    Else
        CreateTable = False
    End If
    
    Exit Function
Err:
        CreateTable = False
        MsgBox Err.Number & " " & Err.Description
End Function

This Function will return TRUE if the table is created successfully or FALSE if the table is not created.

You can call the function like this:

Private Sub CreateTable_Example()
   Call CreateTable("f1,f2,f3,f4", "ttest")
End Sub

Delete / Drop Table Function

This function will delete a table if it exists:

Public Function DeleteTableIfExists(TableName As String)
    If Not IsNull(DLookup("Name", "MSysObjects", "Name='" & TableName & "'")) Then
        DoCmd.SetWarnings False
        DoCmd.Close acTable, TableName, acSaveYes
        DoCmd.DeleteObject acTable = acDefault, TableName
        Debug.Print "Table " & TableName & " deleted..."
        DoCmd.SetWarnings True
    End If
End Function

You can call the function like this:

Private Sub DeleteTableIfExists_Example()
   Call DeleteTableIfExists("Table1")
End Sub

AutoMacro | Ultimate VBA Add-in | Click for Free Trial!

Empty Table Function

This function will empty a table if it exists:

Public Function EmptyTable(TableName As String)
    If Not IsNull(DLookup("Name", "MSysObjects", "Name='" & TableName & "'")) Then
        DoCmd.SetWarnings False
        DoCmd.RunSQL "DELETE * FROM " & TableName
        Debug.Print "Table " & TableName & " emptied..."
        DoCmd.SetWarnings True
    End If
End Function

You can call the function like this:

Private Sub EmptyTable_Example()
   Call EmptyTable("Table1")
End Sub

Rename Table Function

This VBA function will rename a table:

Public Function RenameTable(ByVal strOldTableName As String, ByVal strNewTableName As String, Optional strDBPath As String) As Boolean
    Dim db As DAO.Database
    Dim tdf As TableDef

    ' Trap for any errors.
    On Error Resume Next

    ' If the database name is empty...
    If Trim$(strDBPath) = "" Then
        ' ...then set Db to the current Db.
        Set db = CurrentDb()
    Else
        ' Otherwise, set Db to the specified open database.
        Set db = DBEngine.Workspaces(0).OpenDatabase(strDBPath)

        ' See if an error occurred.
        If Err Then
            'MsgBox "Could not find database to open: " & strDBPath
            RenameTable = False
            Exit Function
        End If
    End If

    If ObjectExists("Table", strOldTableName, strDBPath) Then
        Set tdf = db.TableDefs(strOldTableName)
        tdf.Name = strNewTableName
        db.Close
        RenameTable = True
    Else
        RenameTable = False
    End If
End Function

'Usage Example
Private Sub RenameTable_Example()
    Call RenameTable("table1", "table2")
End Sub

You can call the function like this:

Private Sub RenameTable_Example()
    Call RenameTable("table1", "table2")
End Sub

Truncate / Delete Records from Table

This function will delete records from a table with error handling:

Public Function Delete_From_Table(TableName As String, Criteria As String)
    On Error GoTo SubError
    
    DoCmd.SetWarnings False
    DoCmd.RunSQL ("DELETE * FROM " & TableName & " WHERE " & Criteria)
    DoCmd.SetWarnings True
    
SubExit:
    Exit Function
SubError:
    MsgBox "Delete_From_Table error: " & vbCrLf & Err.Number & ": " & Err.Description
    Resume SubExit
End Function

'Usage Example
Public Sub Delete_From_Table_Example()
 Call Delete_From_Table("Table1", "num=2")
End Sub

Export Table to Excel

This line of code will export a Table to Excel (a new spreadsheet):

DoCmd.OutputTo acOutputTable, "Table1", acFormatXLS, "c:\temp\ExportedTable.xls"

Or you can use this function:

Public Function Export_Table_Excel(TableName As String, FilePath As String)
    DoCmd.TransferSpreadsheet acExport, acSpreadsheetTypeExcel9, TableName, FilePath, True
End Function

'Usage Example
Sub Export_Table_Excel_Example ()
    Export_Table_Excel("Table1", "c:\temp\ExportedTable.xls")
End Sub

The above code will export to a new spreadsheet. Instead you can add a table to an existing spreadsheet. Our article on Importing / Exporting in Access VBA covers this in more detail.

AutoMacro | Ultimate VBA Add-in | Click for Free Trial!

Add / Append Records to a Table

This function will add / append a record to a table:

Public Function Append_Record_To_Table(TableName As String, FieldName As String, FieldValue As String)
    On Error GoTo SubError
    
    Dim rs As DAO.Recordset
    Dim SQL As String
    Dim CurrentYear As Integer
    
    Set rs = CurrentDb.OpenRecordset(TableName)
    
    rs.AddNew
    rs(FieldName).Value = FieldValue
    rs.Update
    
    rs.Close
    Set rs = Nothing
    
SubExit:
    Exit Function
SubError:
    MsgBox "RunSQL error: " & vbCrLf & Err.Number & ": " & Err.Description
    Resume SubExit
End Function

'Usage Example
Private Sub Append_Record_To_Table_Example()
    Call Append_Record_To_Table("Table1", "num", 3)
End Sub

Add Record to Table From Form

This function will add a record to a table from a form:

Public Function Add_Record_To_Table_From_Form(TableName As String)
    On Error GoTo SubError
    
    Dim rs As DAO.Recordset
    
    Set rs = CurrentDb.OpenRecordset(TableName)
    rs.AddNew
    'rs![Field1] = Value1
    'rs![Field2] = Value2
    'rs![Field3] = Value3
    rs.Update
    
    rs.Close
    Set rs = Nothing
    
SubExit:
    Exit Function
SubError:
    MsgBox "Refresh_Form error: " & vbCrLf & Err.Number & ": " & Err.Description
    
End Function

 

 

vba-free-addin

VBA Code Examples Add-in

Easily access all of the code examples found on our site.

Simply navigate to the menu, click, and the code will be inserted directly into your module. .xlam add-in.

(No installation required!)

Free Download

Return to VBA Code Examples