Man is a slow, sloppy, and brilliant thinker; computers are fast, accurate, and stupid.
- John Pfeiffer

Top Ten Tags

Who's Online

Besides the common practice of controlling the status bar text or displaying a progress meter in Microsoft Access, the SysCmd command may be used for other purposes.

  • Return Access system information
  • Return the state of a database object (What is the state of a form / query / report / table? Is it Open, Not open / does not exist, Dirty (changed but not saved), or New?

VBA CODE 

Option Compare Database
Option Explicit

Sub UsingSysCmd()

    Dim retval As Variant

    'RETURNING MS ACCESS INFORMATION
    Debug.Print "MS ACCESS - Information"
    
    retval = SysCmd(acSysCmdAccessVer)
    Debug.Print "Access Version Number = " & retval
    
    retval = SysCmd(acSysCmdGetWorkgroupFile)
    Debug.Print "The path to the workgroup file = " & retval
    
    retval = SysCmd(acSysCmdRuntime)
    Debug.Print "Runtime version? =  " & retval
    
    retval = SysCmd(acSysCmdAccessDir)
    Debug.Print "Folder that contains Msaccess.exe = " & retval
    
    retval = SysCmd(acSysCmdProfile)
    Debug.Print "/profile setting specified " & _
                "when starting Access from command line = " & retval
    
    Debug.Print " "

    'RETURNING OBJECT STATES
    '
    'Possible object types are
    ' - acTable
    ' - acQuery
    ' - acForm
    ' - acReport
    ' - acMacro
    ' - acModule
    ' - acDataAccessPage
    ' - acDefault
    ' - acDiagram
    ' - acServerView
    ' - acFunction
    ' - acStoredProcedure
    '
    'Return values can be any of the following:
    '0  = Not open or does not exist
    '1  = Open
    '2  = Changed but not saved
    '4  = New


    Dim obj As AccessObject, dbs As Object
    Set dbs = Application.CurrentData

    'Tables
    Debug.Print "Num of Tables = " & dbs.AllTables.Count
    For Each obj In dbs.AllTables
        retval = SysCmd(acSysCmdGetObjectState, acTable, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    'Queries
    Debug.Print "Num of Queries = " & dbs.AllQueries.Count
    For Each obj In dbs.AllQueries
        retval = SysCmd(acSysCmdGetObjectState, acQuery, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    Set dbs = Application.CurrentProject

    'Forms
    Debug.Print "Num of Forms = " & dbs.AllForms.Count
    For Each obj In dbs.AllForms
        retval = SysCmd(acSysCmdGetObjectState, acForm, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    'Reports
    Debug.Print "Num of Reports = " & dbs.AllReports.Count
    For Each obj In dbs.AllReports
        retval = SysCmd(acSysCmdGetObjectState, acReport, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    'Macros
    Debug.Print "Num of Macros = " & dbs.AllMacros.Count
    For Each obj In dbs.AllMacros
        retval = SysCmd(acSysCmdGetObjectState, acMacro, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    'Modules
    Debug.Print "Num of Modules = " & dbs.AllModules.Count
    For Each obj In dbs.AllModules
        retval = SysCmd(acSysCmdGetObjectState, acModule, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

    'Data Access Pages
    Debug.Print "Num of Data Access Pages = " & _
                dbs.AllDataAccessPages.Count
    For Each obj In dbs.AllDataAccessPages
        retval = SysCmd(acSysCmdGetObjectState, acDataAccessPage, obj.Name)
        Debug.Print obj.Name & " - " & retval & _
                    " (" & ObjStateDesc(Int(retval)) & ")"
    Next obj
    Debug.Print " "

End Sub

Function ObjStateDesc(intState As Integer) As String

    '************************************************************
    'CONSTANT,          STATE OF DATABASE,          OBJECT VALUE
    '
    'acObjStateOpen,    Open,                       1
    'acObjStateDirty,   Changed but not saved,      2
    'acObjStateNew,     New,                        4
    '
    'Note: Object can be in more than one state,
    '   e.g. acObjStateOpen and acObjStateDirty, 1 + 2 = 3,
    '   i.e. in binary 01 and 10 = 11
    '************************************************************

    Select Case intState
    Case 0
        ObjStateDesc = "Not open or does not exist"
    Case 1    'acObjStateOpen
        ObjStateDesc = "Open"
    Case 2    'acObjStateDirty
        ObjStateDesc = "Dirty (Changed but not saved)"
    Case 3    'acObjStateOpen & acObjStateNew
        ObjStateDesc = "Open & Dirty (Changed but not saved)"
    Case 4    'acObjStateNew
        ObjStateDesc = "New"
    Case 5   'acObjStateOpen & acObjStateNew _
              (Not sure if this can happen since an object _
               is only new when it 's first open and not yet saved)
        ObjStateDesc = "New & Open"
    Case Else
        ObjStateDesc = "Invalid Obj State"
    End Select

End Function

Links

Sample File
Download the sample file.
SysCmd Method [Access 2003 VBA Language Reference]
https://msdn.microsoft.com/en-us/library/office/aa221609(v=office.11).aspx
Application.SysCmd Method (Access)
https://msdn.microsoft.com/en-us/vba/access-vba/articles/application-syscmd-method-access