VBA Class Basics (Report Class)

Collapse
X
 
  • Time
  • Show
Clear All
new posts
  • NeoPa
    Recognized Expert Moderator MVP
    • Oct 2006
    • 32648

    VBA Class Basics (Report Class)

    Introduction
    For this article I'll be focusing on the Report (clsReport) class. This simply handles making the calling Form invisible until all of the Reports opened by it have been closed, when it then makes that (calling) Form visible again. This article is released as a companion to the VBA Class Basics one that focuses on opening Forms. All Forms are shown in Restore mode while Reports are shown in Maximise mode.


    Working Attachment
    Please find attached, a ZIP file that contains the working example called "UKAUG202311.Ac cDb". This is the same file already made available for the other (companion) article. Feel free to download it and have a play with it; make sure you understand what it's doing. You may have no desire to do what it does. What I'm hoping to show is the concept behind it and how classes are used in this case - in order that you understand where, and how, they can be used to do things you want to do.


    VBA Classes with Objects
    This section is repeated verbatim in the other article.
    Although VBA classes do not support the generally-understood concept of Encapsulation, they do allow for objects to be contained within the class code, as well as, importantly, their Events to be handled by the class.

    There is a caveat to this however, and that is that Events can only be handled by the class, that already have Event procedures in the objects themselves. Thus you could have two different Forms used by two different instances of a class (or even the same instance at different times) where one could have its Event handled by the class but the other not, if the first form had a procedure for the Event but the second did not.


    Class/Object Events
    This section is repeated in the other article with only line number reference changes.
    User Defined Classes can also define their own Events. Events support passing parameters and, by using the ByRef keyword, these can be used to pass information both ways. A class needs to both define the Event, as well as Raise it (using RaiseEvent). Be aware that IntelliSense is a little less helpful than usual with this statement (RaiseEvent)so you may have to type it out in full in order to use it. Examples of defining & raising the Events can be found in the code below at lines #14, #15, #145 & #147.


    Class/Object Properties
    This section is repeated verbatim in the other article.
    Coding Propertys within a Class is done using the three Property procedure types shown below. Each comes with an example definition & usage :
    1. Property Let
      This allows a Class-User to assign a value to this Property in the same way they would assign a value to any normal variable. This does not support objects - just as you can't simply say A = B with object variables (but have to use Set).
      Code:
      [U]Definition[/U]
      Private lngVar As Long
      
      Public Property Let Y(Z As Long)
          lngVar = Z
      End Property
      
      [U]Usage (from outside of the Class module)[/U]
      Dim X As YourClass
      
      X.Y = 326
      Notice how the 326 is passed as Z in the Property Let definition and that the variable is referenced within the Class module as lngVar rather than Y.
    2. Property Get
      This is essentially the reverse of Property Let, except it also works for Objects.
      Code:
      [U]Definition[/U]
      Private lngVar As Long
      
      Public Property Get Y() As Long
          Y = lngVar
      End Property
      
      [U]Usage (from outside of the Class module)[/U]
      Dim lngA As Long
      Dim X As YourClass
      
      lngA = X.Y
    3. Property Set
      This is like Property Let except for assigning Objects.
      Code:
      [U]Definition[/U]
      Private frmVar As Form
      
      Public Property Set Y(Z As Form)
          Set frmVar = Z
      End Property
      
      [U]Usage (from outside of the Class module)[/U]
      Dim X As YourClass
      
      Set X.Y = Forms("frmMain")



    clsReport Code
    Here is the code from that class (clsReport). Feel free to copy it to somewhere more visible, and thus have it to hand, while you go through this section.
    NB. When I refer to parts of the code I will do so via the line numbers as shown here below.
    Code:
    Option Compare Database
    Option Explicit
    
    '21/1/2004  Added Private Set & Public Get code for rpt1, 2 & 3.
    '21/9/2004  Removed ResumeTo functionality. _
                Now handled by the OnTimer() subroutine in the calling form _
                checking for (Visible) which indicates the called report is _
                finished.
    '3/11/2023  Added the AllClosed Event to let the calling code (optionally) be
    '           notified when all the Reports have been closed.
    '           Parameter (strName) defined purely for illustration of
    '           the capabilities, but it serves no real purpose.
    
    'Public Event AllClosed()
    Public Event AllClosed(ByRef strName As String)
    
    Private Const conNumRpts As Integer = 3
    Private Const conErrMsg As String = "Maximum number of reports exceeded!"
    
    Private strInUse As String * conNumRpts
    
    Private frmParent As Form
    Private WithEvents rpt01 As Report
    Private WithEvents rpt02 As Report
    Private WithEvents rpt03 As Report
    
    Private Property Set rpt1(rptValue As Report)
        Set rpt01 = rptValue
    End Property
    
    Public Property Get rpt1() As Report
        Set rpt1 = rpt01
    End Property
    
    Private Property Set rpt2(rptValue As Report)
        Set rpt02 = rptValue
    End Property
    
    Public Property Get rpt2() As Report
        Set rpt2 = rpt02
    End Property
    
    Private Property Set rpt3(rptValue As Report)
        Set rpt03 = rptValue
    End Property
    
    Public Property Get rpt3() As Report
        Set rpt3 = rpt03
    End Property
    
    Public Property Set frmFrom(frmValue As Form)
        Set frmParent = frmValue
    End Property
    
    Private Property Get frmFrom() As Form
        Set frmFrom = frmParent
    End Property
    
    'Uninitialised returns True if frmFrom not yet set.
    Public Function Uninitialised() As Boolean
        Uninitialised = (frmParent Is Nothing)
    End Function
    
    'ShowReport opens report strRpt and hides the calling form.
    'Returns True on success.
    Public Function ShowReport(strRpt As String, _
                               Optional ByVal varWhere As Variant = "") As Boolean
        Dim intIdx As Integer
    
        ShowReport = True
        'Error routine only handles Raised error and OpenReport()
        On Error GoTo ErrorSR
        intIdx = InStr(1, strInUse, vbNullChar)
        If Uninitialised() _
        Or intIdx < 1 Then _
            Call Err.Raise(Number:=32767&, Description:=conErrMsg)
        Call Echo(True, "Preparing report [" & strRpt & "].")
        If IsNull(varWhere) Or varWhere = "" Then
            Call DoCmd.OpenReport(ReportName:=strRpt, View:=acViewPreview)
        Else
            Call DoCmd.OpenReport(ReportName:=strRpt _
                                , View:=acViewPreview _
                                , WhereCondition:=varWhere)
        End If
        On Error GoTo 0
        Select Case intIdx
        Case 1
            Set rpt1 = Reports(strRpt)
        Case 2
            Set rpt2 = Reports(strRpt)
        Case 3
            Set rpt3 = Reports(strRpt)
        End Select
        frmFrom.Visible = False
        Mid(strInUse, intIdx, 1) = "*"
        Call DoCmd.Maximize
        Call Echo(True, "Report """ & strRpt & """ ready.")
        Exit Function
    
    ErrorSR:
        ShowReport = False
        Call Echo(True, "")
        If ErrorHandler(strName:=strRpt, _
                        strFrom:=frmFrom.Name & ".ShowReport", _
                        lngErrNo:=Err.Number, _
                        strDesc:=Err.Description) = 2 Then Resume
    End Function
    
    '************************* Contained Object Method(s) **************************
    'For these subroutines to be activated the contained object must have the
    ''On Close' property set to a valid subroutine within the contained object.
    '*******************************************************************************
    'Equivalent to rpt1_Close()
    Private Sub rpt01_Close()
        Set rpt01 = Nothing
        Call CloseReport(1)
    End Sub
    
    'Equivalent to rpt2_Close()
    Private Sub rpt02_Close()
        Set rpt02 = Nothing
        Call CloseReport(2)
    End Sub
    
    'Equivalent to rpt3_Close()
    Private Sub rpt03_Close()
        Set rpt03 = Nothing
        Call CloseReport(3)
    End Sub
    
    'CloseReport() examines the current state of the reports and, only if all now
    '   closed, returns to viewing the parent form.
    '   Resume to the calling code is done using the AllClosed Event which can,
    '   optionally, be handled by the caller.
    Private Sub CloseReport(ByVal intIdx As Integer)
        Dim strParent As String
    
        Mid(strInUse, intIdx, 1) = vbNullChar
        If strInUse = String(conNumRpts, vbNullChar) Then
            Call DoCmd.Restore
            With frmParent
                .Visible = True
                Call DoCmd.SelectObject(acForm, .Name)
            End With
            'RaiseEvent AllClosed
    ' All code after here is for illustration of updateable parameter only.
            RaiseEvent AllClosed(strParent)
            If strParent > "" Then _
                Call MsgBox(Prompt:=strParent _
                          , Buttons:=vbInformation Or vbOKOnly _
                          , Title:="clsReport")
        End If
    End Sub
    '*******************************************************************************
    The code above contains much code that is either repeated, or repeated with minor modifications, from the other article.

    Lines #17 - #18 defines constants used in the code elsewhere. This version allows for three Reports to be opened simultaneously and managed together by this class. With minor modifications elsewhere, to support the extra objects required, this value can be increased to suit needs.

    Line #20 defines a fixed-length String used for maintaining the status of each possible Report object within the class.

    Lines #22 - #25 show two different ways to define objects in VBA. #23 - #25 are different & special as they allow Events from the objects (In this case Reports obviously.) to be handled within this class. See lines #109 - #129 of this module for the format of a class's handling of its various WithEvents objects. Notice the names of the Event Procedures include the (internal) names of the specified objects.

    Lines #27 - #57 show examples of Property Let/Get/Set procedures. These are explained above under Class/Object Properties.

    Lines #59 - #62 show the Uninitialised() function. Any user of the class must set the value of the frmParent Property before anything else can work sensibly. This function is provided to test that.

    Lines #64 - #107 show the ShowReport() Method. This roughly mirrors the DoCmd.OpenRepor t() Method - at least the parameters I ever use. It explicitly handles the Report failing to open but passes any other errors onto the main error handler, which I don't cover here (as irrelevant). However, the code can be found in the attached example database if interested.

    Fundamentally, it checks the class instance has been properly initialised then, if it has, Maximises the window before opening the Report, using the parameters as passed. Once this has succeeded it sets the next rpt? (where ?=1, 2 or 3) to this Report and hides the parent/calling Form.

    Lines #109 - #153 handle the Close events of the called Reports (internally referenced as rpt0? - hence the names of rpt0?_Close()). Once they close, this procedure first sets the relevant object (rpt0?) to Nothing, then checks if any are still open. If, and only if, none is, then the parent/calling Form (frmParent) is made visible again. For good measure it Restores the window again. The working basis is that Forms look better in Restore mode while Reports look better Maximised.


    Conclusion
    While the attached example database also includes a clsForm class, along with the clsReport one as shown here, the fundamentals of class usage, & I hope I've kept to the very basics in order to show how straightforward it is getting into the subject, are covered here.

    Feel free to leave comments below, but please post any related questions separately (in the Access Questions Forum). Also, feel free to use any parts of this work. Attribution is purely voluntary.
    Last edited by NeoPa; Nov 6 '23, 05:45 PM.
Working...