Application.RefreshTitleBar method (Access)
The RefreshTitleBar method refreshes the Microsoft Access title bar after the AppTitle or AppIcon property has been set in Visual Basic.
Syntax
expression.RefreshTitleBar
expression A variable that represents an Application object.
Return value
Nothing
Remarks
For example, you can change the caption in the Microsoft Access title bar to "Contacts Database" by setting the AppTitle property.
The AppTitle and AppIcon properties enable you to customize your application by changing the title and icon that appear in the Access title bar. The title bar is not automatically updated after you set these properties. For the change to the title bar to appear, you must use the RefreshTitleBar method.
Note
In an Access database, you can reset the AppTitle and AppIcon properties to their default values by deleting them from the Properties collection representing the current database. After you delete these properties, you must use the RefreshTitleBar method to restore the Access defaults to the title bar.
If the path to the icon specified by the AppIcon property is invalid, no changes will be reflected in the title bar when you call this method.
Example
The following example sets the AppTitle property of the current database and applies the RefreshTitleBar method to update the title bar.
Sub ChangeTitle()
Dim obj As Object
Const conPropNotFoundError = 3270
On Error GoTo ErrorHandler
' Return Database object variable pointing to
' the current database.
Set dbs = CurrentDb
' Change title bar.
dbs.Properties!AppTitle = "Contacts Database"
' Update title bar on screen.
Application.RefreshTitleBar
Exit Sub
ErrorHandler:
If Err.Number = conPropNotFoundError Then
Set obj = dbs.CreateProperty("AppTitle", dbText, "Contacts Database")
dbs.Properties.Append obj
Else
MsgBox "Error: " & Err.Number & vbCrLf & Err.Description
End If
Resume Next
End Sub
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.