People think computers will keep them from making mistakes. They're wrong. With computers you make mistakes faster. - Adam Osborne

Top Ten Tags

Who's Online

VBA Functions that use DAO to do the following:

IsTable()
Determine if table exists in an Access database
IsQuery()
Determine if query exists in an Access database
IsField()
Determine if field exists in an Access database table/query
IsFieldProperty()
Determine if property for a table/query field exists

Example Usage

See ExampleUsage() in 'modExample' in the sample file for complete examples of how to use the functions.

Debug.Print "IsTable('" & strName & "') = " & IsTable(strName)

'or 

Dim db as DAO.Database, strName as string
Set db = CurrentDb
strName = "tblData"
Debug.Print "IsTable('" & strName & "', db) = " & IsTable(strName, db)

VBA Code

Option Compare Database


Public Function IsTable(ByVal strTableName As String, _
                        Optional ByVal dbDatabase As DAO.Database) As Boolean
    
    '**********************************************************
    'Function: Determine if table exists in an Access database
    '
    'Arguments:
    '   strTablename:   Name of table to check
    '   dbDatabase:     (Optional) DAO database object
    '                   Defaults to CurrentDB if not passed
    '**********************************************************

    Dim tdf As DAO.TableDef
    
    If dbDatabase Is Nothing Then Set dbDatabase = CurrentDb

    On Error Resume Next
    Set tdf = dbDatabase.TableDefs(strTableName)
    IsTable = (Err.Number = 0)

End Function


Public Function IsQuery(ByVal strQueryName As String, _
                        Optional ByVal dbDatabase As DAO.Database) As Boolean

    '**********************************************************
    'Function: Determine if query exists in an Access database
    '
    'Arguments:
    '   strQueryName:   Name of query to check
    '   dbDatabase:     (Optional) DAO database object
    '                   Defaults to CurrentDB if not passed
    '**********************************************************
    
    Dim qdf As DAO.QueryDef

    On Error Resume Next
    Set qdf = dbDatabase.QueryDefs(strQueryName)
    IsQuery = (Err.Number = 0)

End Function


Public Function IsField(strObjectName As String, _
                        strFieldName As String, _
                        Optional strObjectType As String = "Table", _
                        Optional ByVal dbDatabase As DAO.Database) _
                        As Boolean

    '**********************************************************************
    'Function: Determine if field exists in an Access database table/query
    '
    'Arguments:
    '   strObjectName:  Name of the table/query containing the field
    '   strFieldName:   Name of the field
    '   dbDatabase:     (Optional) DAO database object
    '                   Defaults to CurrentDB if not passed
    '**********************************************************************
    
    On Error Resume Next
    
    IsField = False
    
    Select Case strObjectType
    Case "Table"
        IsField = (LenB(dbDatabase.TableDefs(strObjectName).Fields(strFieldName).Name) > 0)
    Case "Query"
        IsField = (LenB(dbDatabase.QueryDefs(strObjectName).Fields(strFieldName).Name) > 0)
    End Select
        
    IsField = (Err.Number = 0)

End Function


Public Function IsFieldProperty(ByVal DAOField As DAO.Field, strPropertyName As String) _
                As Boolean

    '****************************************************************
    'Function: Determine if property for a table/query field exists
    '
    'Arguments:
    '   DAOField:          DAO field oject
    '   strPropertyName:   Name of the property to check if it exists
    '****************************************************************
    
    On Error Resume Next
    
    IsFieldProperty = (Len(DAOField.Properties(strPropertyName)) > 0)
        
    IsFieldProperty = (Err.Number = 0)

End Function

Sample File

Download the sample file.