Dump table details in VBA (DAO)

        31 votes: *****     49,661 views      5 comments
by Allen Browne, 20 April 2005    (for Access 95+)

Microsoft Access: VBA Programming Code

Provided by Allen Browne, allenbrowne.com. Updated June 2006.


TableInfo() function

This function displays in the Immediate Window (Ctrl+G) the structure of any table in the current database.
For Access 2000 or 2002, make sure you have a DAO reference.
The Description property does not exist for fields that have no description, so a separate function handles that error.

The code


Function TableInfo(strTableName As String)
On Error GoTo TableInfoErr
   ' Purpose:   Display the field names, types, sizes and descriptions for a table.
   ' Argument:  Name of a table in the current database.
   Dim db As DAO.Database
   Dim tdf As DAO.TableDef
   Dim fld As DAO.Field
   
   Set db = CurrentDb()
   Set tdf = db.TableDefs(strTableName)
   Debug.Print "FIELD NAME", "FIELD TYPE", "SIZE", "DESCRIPTION"
   Debug.Print "==========", "==========", "====", "==========="

   For Each fld In tdf.Fields
      Debug.Print fld.Name,
      Debug.Print FieldTypeName(fld),
      Debug.Print fld.Size,
      Debug.Print GetDescrip(fld)
   Next
   Debug.Print "==========", "==========", "====", "==========="

TableInfoExit:
   Set db = Nothing
   Exit Function

TableInfoErr:
   Select Case Err
   Case 3265&  'Table name invalid
      MsgBox strTableName & " table doesn't exist"
   Case Else
      Debug.Print "TableInfo() Error " & Err & ": " & Error
   End Select
   Resume TableInfoExit
End Function


Function GetDescrip(obj As Object) As String
    On Error Resume Next
    GetDescrip = obj.Properties("Description")
End Function


Function FieldTypeName(fld As DAO.Field) As String
    'Purpose: Converts the numeric results of DAO Field.Type to text.
    Dim strReturn As String    'Name to return

    Select Case CLng(fld.Type) 'fld.Type is Integer, but constants are Long.
        Case dbBoolean: strReturn = "Yes/No"            ' 1
        Case dbByte: strReturn = "Byte"                 ' 2
        Case dbInteger: strReturn = "Integer"           ' 3
        Case dbLong                                     ' 4
            If (fld.Attributes And dbAutoIncrField) = 0& Then
                strReturn = "Long Integer"
            Else
                strReturn = "AutoNumber"
            End If
        Case dbCurrency: strReturn = "Currency"         ' 5
        Case dbSingle: strReturn = "Single"             ' 6
        Case dbDouble: strReturn = "Double"             ' 7
        Case dbDate: strReturn = "Date/Time"            ' 8
        Case dbBinary: strReturn = "Binary"             ' 9 (no interface)
        Case dbText                                     '10
            If (fld.Attributes And dbFixedField) = 0& Then
                strReturn = "Text"
            Else
                strReturn = "Text (fixed width)"        '(no interface)
            End If
        Case dbLongBinary: strReturn = "OLE Object"     '11
        Case dbMemo                                     '12
            If (fld.Attributes And dbHyperlinkField) = 0& Then
                strReturn = "Memo"
            Else
                strReturn = "Hyperlink"
            End If
        Case dbGUID: strReturn = "GUID"                 '15

        'Attached tables only: cannot create these in JET.
        Case dbBigInt: strReturn = "Big Integer"        '16
        Case dbVarBinary: strReturn = "VarBinary"       '17
        Case dbChar: strReturn = "Char"                 '18
        Case dbNumeric: strReturn = "Numeric"           '19
        Case dbDecimal: strReturn = "Decimal"           '20
        Case dbFloat: strReturn = "Float"               '21
        Case dbTime: strReturn = "Time"                 '22
        Case dbTimeStamp: strReturn = "Time Stamp"      '23

        'Constants for complex types don't work prior to Access 2007.
        Case 101&: strReturn = "Attachment"         'dbAttachment
        Case 102&: strReturn = "Complex Byte"       'dbComplexByte
        Case 103&: strReturn = "Complex Integer"    'dbComplexInteger
        Case 104&: strReturn = "Complex Long"       'dbComplexLong
        Case 105&: strReturn = "Complex Single"     'dbComplexSingle
        Case 106&: strReturn = "Complex Double"     'dbComplexDouble
        Case 107&: strReturn = "Complex GUID"       'dbComplexGUID
        Case 108&: strReturn = "Complex Decimal"    'dbComplexDecimal
        Case 109&: strReturn = "Complex Text"       'dbComplexText
        Case Else: strReturn = "Field type " & fld.Type & " unknown"
    End Select

    FieldTypeName = strReturn
End Function

Home Index of tips Top

Rate this article:  Your rating: PoorYour rating: Not so goodYour rating: AverageYour rating: GoodYour rating: Excellent


This is a cached tutorial, reproduced with permission.

Have your say - comment on this article.

What did you think of 'Dump table details in VBA (DAO)'?


1.

v. says...

21 May 2009

 
EXACTLY what I needed. Thanks for taking the time and trouble to publish this.

2.

Chris says...

03 Feb 2010

 
tidy little function, thanks for that. I needed something to show the required property and this exposed it nicely (Debug.Print fld.Required)

3.

David says...

05 May 2010

 
Good function and you know what makes it even more useful. Create a table called StructuresTbl, with fields: TableName, FieldName, FieldType, Size and Description Instead of Debug.Print, add code to INSERT INTO the StructuresTbl in the FOR NEXT loop, then you have a nice clean organized table of structures that you can export to Excel or create a data dictionary with.

4.

Jack says...

27 Oct 2010

 
Sweet piece of work. I haven't looked at msaccess for a long time and this just saved me a bundle of hours. Thanks. And David's enhancement is slick, too. Thanks!

5.

Adrian says...

13 Nov 2010

 
Nice work. People like you are the hope of mankind. Thank you for sharing your time with us.

Have your say...

Name
E-mail (e-mail address will be kept private)
Comments


Comments require approval before being displayed on this page (allow 24 hours).