I changed my password everywhere to 'incorrect.' That way when I forget it, it always reminds me, 'Your password is incorrect.'
- Anonymous

Top Ten Tags

Who's Online

This is code from a Microsoft KB article - KB Article 210398. I can't find it anywhere online (except for the Internet Archive) so I'm posting it here for reference along with the pertinent text from that article.

Summary

This article contains a sample user-defined function named IsTableQuery() that you can use to determine whether a table or a query exists in a database. The sample function uses the TableDefs and QueryDefs Data Access Objects (DAO) collections.

NOTE: 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. To do so, click References on the Tools menu in the Visual Basic Editor, and make sure that the correct Object Library reference check box is selected.

VBA Code

Option Compare Database

'********************************************************
' FUNCTION: IsTableQuery()
'
' PURPOSE: Determine if a table or query exists.
'
' ARGUMENTS:
'   DbName: The name of the database. If the database name
'           is "" the current database is used.
'    TName: The name of a table or query.
'
' RETURNS: True (it exists) or False (it does not exist).
'
'********************************************************

Function IsTableQuery(DbName As String, TName As String) As Integer

Dim Db As DAO.Database, Found As Integer, Test As String
Const NAME_NOT_IN_COLLECTION = 3265

' Assume the table or query does not exist.
Found = False

' Trap for any errors.
On Error Resume Next

' If the database name is empty...
If Trim$(DbName) = "" 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(DbName)

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

' See if the name is in the Tables collection.
Test = Db.TableDefs(TName).Name
If Err <> NAME_NOT_IN_COLLECTION Then Found = True

' Reset the error variable.
Err = 0

' See if the name is in the Queries collection.
Test = Db.QueryDefs(TName$).Name
If Err <> NAME_NOT_IN_COLLECTION Then Found = True

Db.Close

IsTableQuery = Found

End Function