Home  |   French  |   About  |   Search  | mvps.org  

What's New
Table Of Contents
Credits
Netiquette
10 Commandments 
Bugs
Tables
Queries
Forms
Reports
Modules
APIs
Strings
Date/Time
General
Downloads
Resources
Search
Feedback
mvps.org

In Memoriam

Terms of Use


VB Petition

Forms: Update All Open Forms

Author(s)
Mitch Wheat

(Q) When I change database data through code, how do I ensure that all open data-bound forms display the latest values?

(A) In order to requery each form's underlying recordset, you could loop through the forms and requery individually. I found problems with this approach; sometimes the requery would not contain the latest data unless I first closed the form. The safest way to ensure that current data is displayed (though not the most efficient) is to close all forms and re-open them, but this would leave each form reset to the first record. The following code checks which forms are open, and tries to create a unique filter string for the current record in order to move the forms bookmark on re-opening.

- To call this routine, just pass in the name of the form you do not want updating (usually the calling form)

UpdateAllOpenForms Me.Name

(this could be improved by passing in a comma delimited list of forms you do not want updating)

'************* Code Start **************
' This code was originally written by Mitch Wheat
' It is not to be altered or distributed,
' except as part of an application.
' You are free to use it in any application,
' provided the copyright notice is left unchanged.
'
' Code Courtesy of
' Mitch Wheat
'
' Update all open data-bound forms by first closing
' them and then re-opening at the same record.
'
' This code was written by Mitch Wheat
' Jan 16, 1999.
'
' You are free to distribute and use this code as you wish
' but please credit the original author (by leaving this notice intact).
'

Public Sub UpdateAllOpenForms(ByVal strFormName As String)
    Const cstrProcName As String = mcstrModuleName & "UpdateAllOpenForms"
    Dim frm As Form
    Dim rs As Recordset
    Dim fld As Field
    Dim lngFormcount As Long
    Dim i As Long
    Dim strCriteria As String
    Dim varr() As Variant
    Const conDesignView As Long = 0
    
    ' Ignore any errors...
    On Error Resume Next
    
    ReDim varr(Forms.Count, 2)
    
    ' Update any open forms...
    i = 0
    lngFormcount = 0
    For Each frm In Forms
        With frm
            If .FormName <> strFormName And .CurrentView <> conDesignView Then
                strCriteria = vbNullString
                Set rs = .RecordsetClone
                ' Ignore non-data bound forms...
                If Not (rs Is Nothing) Then
                    rs.Bookmark = .Bookmark
                    
                    ' First look for Identity field...
                    For Each fld In rs.Fields
                        If (fld.Attributes And dbAutoIncrField) = dbAutoIncrField Then
                            strCriteria = "[" & fld.Name & "]=" & fld.Value
                            ' Found identity (autonumber) field, so exit...
                            Exit For
                        End If
                    Next
                    
                    ' If Identity field not found, generate criteria that will locate the current record...
                    If Len(strCriteria) = 0 Then
                        For Each fld In rs.Fields
                            If IsNull(fld.Value) = False Then
                                ' Just use numeric fields (you could alter this to include string and date)...
                                If fld.Type = dbLong Then
                                    strCriteria = strCriteria & "(" & "[" & fld.Name & "]=" & fld.Value & ") AND "
                                End If
                            End If
                        Next
                        If Len(strCriteria) > 0 Then strCriteria = Left$(strCriteria, Len(strCriteria) - 5)
                    End If
                    Set rs = Nothing
                    
                    ' If we have criteria, add this form to the list...
                    If Len(strCriteria) > 0 Then
                        lngFormcount = lngFormcount + 1
                        varr(lngFormcount, 1) = .FormName
                        varr(lngFormcount, 2) = strCriteria
                    End If
                End If
            End If
        End With
    Next
    
    ' Close all open forms and reopen at same record...
    For i = 1 To lngFormcount
        DoCmd.Close acForm, varr(i, 1)
        DoCmd.OpenForm varr(i, 1)
        With Forms(varr(i, 1))
            Set rs = .RecordsetClone
            rs.FindFirst varr(i, 2)
            If Not rs.NoMatch Then
                .Bookmark = rs.Bookmark
            End If
            Set rs = Nothing
        End With
    Next
    
    Forms(strFormName).SetFocus
    Erase varr
    
End Sub
'************* Code End **************
 

© 1998-2010, Dev Ashish & Arvin Meyer, All rights reserved. Optimized for Microsoft Internet Explorer