Introduction.
In this Episode of Streamlining Form Module VBA Code, we will create Wrapper Classes for ComboBox and OptionGroup Controls. Having gone through the previous Episodes, you are now acquainted with the process of creating Wrapper Class Modules for other controls, such as TextBox, ListBox, CommandButton, and TabControl. You have also learned to write Event Subroutines within these modules instead of placing them in the Form Module.
ComboBox and OptionGroup Control.
In this session, we will focus on the usage of ComboBox and OptionGroup controls, as illustrated in the form image shown below.
The Order Detail data displayed in the ListBox is filtered through the query OrderDetailQ1, which is based on the Employee ID selected in the ComboBox control named cboEmp, located above the ListBox. The SQL statement for this query is shown below:
OrderDetailQ1 SQL.
SELECT Orders.EmployeeID, Employees.LastName, Orders.OrderID, Val(Format([OrderDate],"yyyy")) AS [Year], Orders.Freight FROM Employees INNER JOIN Orders ON Employees.EmployeeID = Orders.EmployeeID WHERE (((Orders.EmployeeID)=[Forms]![Frm_OptionGroup]![cboEmp]));
The Freight values from OrderDetailQ1 are summarized by year in the query OrderSummaryQ1. This query provides the year-wise Freight totals, which serve as the source data for the Graph Chart displayed on the Form. The SQL statement for OrderSummaryQ1 is shown below:
OrderSummaryQ1 SQL.
SELECT [OrderDetailQ1].EmployeeID, [OrderDetailQ1].LastName, [OrderDetailQ1].Year, Sum([OrderDetailQ1].freight) AS Freight FROM OrderDetailQ1 GROUP BY [OrderDetailQ1].EmployeeID, [OrderDetailQ1].LastName, [OrderDetailQ1].Year;
Freight Summary Data for the Chart.
Employee Last Name Year Freight Davolio, Nancy Davolio 1996 ₹ 1,871.09 Davolio, Nancy Davolio 1997 ₹ 4,584.47 Davolio, Nancy Davolio 1998 ₹ 2,381.13
How are ComboBox, ListBox, and the Chart linked together?
When an Employee is selected in the ComboBox, the AfterUpdate event is triggered, and the statement cbofrm.List0.Requery refreshes the contents of the ListBox.
A hidden unbound TextBox on the Form is used to copy the Employee ID value from the cboEmp ComboBox. This TextBox serves as the Link Master Field for the Graph Chart, ensuring that the year-wise Freight summary updates automatically.
As a result, whenever the Employee selection changes (note that the ComboBox displays only the Employee Name, with the first column EmployeeID hidden by setting its column width to zero), both the OrderDetail ListBox and the year-wise Freight values in the Graph Chart are refreshed instantly.
The OptionGroup Control.
The OptionGroup control can contain a set of Radio Buttons, Check Boxes, or Toggle Buttons, all placed within a common Frame. In this example, we are using Radio Buttons inside an OptionGroup frame named Frame7. The Frame7 control holds three Radio Buttons, each with its own label, and is positioned below the ListBox and Graph objects on the Form.
There are three options to display the Employee's Freight Sales Values in three different categories.
- - The highest Freight Sales Value of the Employee.
- - The Lowest Freight Sales Value.
- - The Total Fright Sales Value.
An Unbound TextBox, placed to the left of the OptionGroup control, displays the value of the selected Radio Button. Next to it, a Label control shows the selected option description. The label text is presented in an animated style, smoothly moving from right to left to highlight the current selection.
The Command Button Click will close the Form.
We already created wrapper classes for the ComboBox and ListBox in the earlier episodes. The OptionGroup Control is new in this Series of Tutorials and needs a Wrapper Class. When we place an OptionGroup Control on the Form, the default name used by Microsoft Access is something like Frame7. We will create a Wrapper Class named OptFrame for the OptionGroup Control.
The OptFrame Wrapper Class VBA Code.
Option Compare Database
Option Explicit
Private WithEvents Opt As Access.OptionGroup
Private frm As Access.Form
'------------------------------------------------------
'Streamlining Form Module Code
'in Stand-alone Class Modules
'------------------------------------------------------
'OptionGroup Wrapper Class
'Author: a.p.r. pillai
'Date  : 31/08/2023
'Rights: All Rights(c) Reserved by www.msaccesstips.com
'------------------------------------------------------
'Form's Property GET/SET Procedures
Public Property Get opt_Frm() As Form
    Set opt_Frm = frm
End Property
Public Property Set opt_Frm(ByRef ofrm As Form)
    Set frm = ofrm
End Property
'TextBox Property GET/SET Procedures
Public Property Get o_opt() As OptionGroup
    Set o_opt = Opt
End Property
Public Property Set o_opt(ByRef mopt As OptionGroup)
    Set Opt = mopt
End Property
'Event Subroutines Code
Private Sub opt_Click()
Dim Rslt As Variant
Dim Cap(1 To 3) As String
Static strText As String
Cap(1) = "Highest Freight Value:"
Cap(2) = " Lowest Freight Value:"
Cap(3) = "  Total Freight Value:"
Select Case Opt.Name
    Case "Frame7"
        Select Case Opt.Value
            Case 1
            'Repeated Clicks on the same option is ignored.
            If strText = Cap(1) Then Exit Sub
                Rslt = DMax("Freight", "OrderDetailQ1")
            Case 2
                If strText = Cap(2) Then Exit Sub
                Rslt = DMin("Freight", "OrderDetailQ1")
                
            Case 3
                If strText = Cap(3) Then Exit Sub
                Rslt = DSum("Freight", "OrderDetailQ1")
        End Select
End Select
       frm!Result = Rslt
       strText = Cap(Opt)
       
       Call Animate(strText) 'Label Animation
End Sub
Private Sub Animate(ByVal txt As String)
'Label Animation
Dim L As Double
Dim n As String
Dim T As Double
Dim j As Integer
L = Len(txt)
txt = Space(L) & txt
For j = 1 To Len(txt) - L
 n = Left(txt, 1)
 txt = Right(txt, Len(txt) - 1)
 txt = txt & n
 frm.lblResult.Caption = Left(txt, L)
    Delay 0.02 'delay 20 milliseconds
Next
End Sub
In the OptFrame Wrapper Class Module, the OptionGroup control object (Opt) is declared with the WithEvents keyword in the global section of the Class Module. Alongside it, a Form object property named frm is also declared. Corresponding Property Procedures are then defined to manage these global properties.
The Opt_Click() Event Subroutine.
Private Sub opt_Click()
Dim Rslt As Variant
Dim Cap(1 To 3) As String
Static strText As String
Cap(1) = "Highest Freight Value:"
Cap(2) = " Lowest Freight Value:"
Cap(3) = "  Total Freight Value:"
Select Case Opt.Name
    Case "Frame7"
        Select Case Opt.Value
            Case 1
                If strText = Cap(1) Then Exit Sub
                Rslt = DMax("Freight", "OrderDetailQ1")
            Case 2
                If strText = Cap(2) Then Exit Sub
                Rslt = DMin("Freight", "OrderDetailQ1")
                
            Case 3
                If strText = Cap(3) Then Exit Sub
                Rslt = DSum("Freight", "OrderDetailQ1")
        End Select
End Select
       frm!Result = Rslt
       strText = Cap(Opt)
       
       Call Animate(strText) 'Label Animation
End Sub
The OptionGroup control on the Form provides three options to extract the Highest, Lowest, and Total Freight Values from the Order Sales transactions. These calculations are applied to the records corresponding to the Employee ID selected in the cboEmp ComboBox.
When an OptionGroup button is clicked, the corresponding Freight value is retrieved from the filtered OrderDetailQ1 data using the appropriate domain aggregate function — DMax(), DMin(), or DSum(). The calculated result is then displayed in the Rslt TextBox, positioned to the left of the OptionGroup control.
The category description of the displayed Freight value is retrieved from the Cap() array, based on the selected OptionGroup control’s Radio Button index. This text is then passed as a parameter to the Animate() subroutine, which displays it on the Label control located to the left of the Rslt TextBox. The text is revealed in an animated style, character by character, moving from right to left until the full description is displayed.
The statement If strText = Cap(n) Then Exit Sub ignores the Animation from repeating when clicked on the Body of the OptionGroup Frame.
The Label Animation.
The Animate() Subroutine Code segment is given below:
Private Sub Animate(ByVal txt As String) 'Label Animation Dim L As Double Dim n As String Dim T As Double Dim j As Integer L = Len(txt) txt = Space(L) & txt 'Add spaces at the left side For j = 1 To Len(txt) - L n = Left(txt, 1) txt = Right(txt, Len(txt) - 1) txt = txt & n frm.lblResult.Caption = Left(txt, L) Delay 0.02 ' Pause 20 Milliseconds Next End Sub
The length of the Parameter value in the Variable txt is calculated and stored in variable L. The parameter variable txt content is modified by adding an equal number of spaces to its original length on the left side.
The Animation Sequence.
The For…Next loop runs up to the original string length stored in variable L. In each iteration, one character is removed from the left side of the string and appended to its right end. The leftmost L characters are then assigned to the Caption property of the lblResult Label control.
After updating the label, the loop introduces a 20-millisecond delay before proceeding to the next iteration. This process repeats until the full description is displayed on the Label control, creating the scrolling animation effect.
The Delay() Function VBA Code in the Standard Module is given below for information:
Public Sub Delay(ByVal Sleep As Double)
Dim T As Double
T = Timer
Do While Timer < T + Sleep
    DoEvents
Loop
End Sub
The OptObject_Init Class Module VBA Code.
Option Compare Database
Option Explicit
Private iFrm As Access.Form
Private LstB As OptListBox
Private txt As OptTextBox
Private Fram As OptFrame
Private wcbo As optCombo
Private wcmd As OptCmdButton
Private Coll As New Collection
'------------------------------------------------------
'Streamlining Form Module Code
'in Stand-alone Class Modules
'------------------------------------------------------
'Combo and Option Group Controls
'Author: a.p.r. pillai
'Date  : 31/08/2023
'Rights: All Rights(c) Reserved by www.msaccesstips.com
'------------------------------------------------------
'Form's Property GET/SET Procedures
Public Property Get m_Frm() As Form
    Set m_Frm = iFrm
End Property
Public Property Set m_Frm(ByRef mfrm As Form)
    Set iFrm = mfrm
    
    iFrm.cboEmp.DefaultValue = iFrm.cboEmp.Column(0, 1)
    iFrm.List0.Requery
Call Class_Init
End Property
'Events Enabling Subroutine
Private Sub Class_Init()
Dim ctl As Control
Const EP = "[Event Procedure]"
For Each ctl In iFrm.Controls 'Scan for Controls
    Select Case TypeName(ctl)
            Case "OptionGroup"
              Select Case ctl.Name
                Case "Frame7" 'Option Group Name
                    Set Fram = New OptFrame 'Create Instance
                    Set Fram.opt_Frm = iFrm 'Assign Form Object
                    Set Fram.o_opt = ctl   'TextBox
                    
                        Fram.o_opt.OnClick = EP
                        
                    Coll.Add Fram 'Save EmpTextBox Class
                    Set Fram = Nothing 'Erase temp Instance
              End Select
        Case "ComboBox"
                    Set wcbo = New optCombo
                    Set wcbo.cbo_Frm = iFrm
                    Set wcbo.c_cbo = ctl
                    
                   wcbo.c_cbo.AfterUpdate = EP
                   wcbo.c_cbo.OnGotFocus = EP
                   wcbo.c_cbo.OnLostFocus = EP
                    
                    Coll.Add wcbo
                    Set wcbo = Nothing
        Case "TextBox"
                    Set txt = New OptTextBox
                    Set txt.tx_Frm = iFrm
                    Set txt.t_Txt = ctl
                    
                        txt.t_Txt.OnGotFocus = EP
                        txt.t_Txt.OnLostFocus = EP
                    
                    Coll.Add txt
                    Set txt = Nothing
                    
        Case "ListBox"
                    Set LstB = New OptListBox
                    Set LstB.lst_Frm = iFrm
                    Set LstB.m_Lst = ctl
                    
                        LstB.m_Lst.OnGotFocus = EP
                        LstB.m_Lst.OnLostFocus = EP
                    
                    Coll.Add LstB
                    Set LstB = Nothing
                    
        Case "CommandButton"
                    Set wcmd = New OptCmdButton
                    Set wcmd.cmd_Frm = iFrm
                    Set wcmd.c_cmd = ctl
                    
                   wcmd.c_cmd.OnClick = EP
                    
                    Coll.Add wcmd
                    Set wcmd = Nothing
    
    End Select
Next
End Sub
Private Sub Class_Terminate()
'Delete Collection Object contents
    Do While Coll.Count > 0
        Coll.Remove 1
    Loop
    
    Set iFrm = Nothing
End Sub 
As with the other Access Object Wrapper Classes, all required objects are declared as Properties in the global area of the Module, followed by their respective Property Procedures.
Once the Form object is assigned to the internal iFrm object in the Set m_frm() Property Procedure, two initialization statements are executed to refresh the ComboBox and ListBox controls, ensuring they load their default values when the form is opened.
After these initializations, the Class_Init() A subroutine is called to complete the setup of the wrapper class.
The procedures written there are explained in detail in earlier episodes, and I am sure you are well-versed in the procedure.
It is worth noting that on the Form, there is only one instance of each control type: ComboBox, ListBox, TextBox, CommandButton, OptionGroup Control, and Chart Object.
Although the Chart object also exposes several events, just like the other controls, it is usually not given as much attention. However, if required, these events can be captured and managed in the same way by creating a dedicated Wrapper Class Module for the Chart control. This ensures the Chart’s interactions and behaviors can also be centralized, making the coding style fully consistent across all Form objects.
When to create a Wrapper Class?
There may be multiple instances of a particular control type on a Form (for example, several TextBox controls). In such cases, using Wrapper Classes becomes essential to capture and manage their individual events in a structured manner.
However, if there is only a single instance of a control type on the Form that requires one or more event procedures, then creating a dedicated Wrapper Class is not strictly necessary. Instead, you can:
- 
Declare the control as a property in the OptObject_Init Class Module (the intermediate class), qualified with the WithEventskeyword.
- 
Assign the control’s reference from the Form within the initialization routine. 
- 
Enable its events and write the required event procedures directly in the OptObject_Init Class Module. 
This approach keeps the codebase cleaner by avoiding unnecessary Wrapper Classes, while still maintaining event-driven consistency for all controls.
Since the OptionGroup Control (Frame7) is a new addition in the Streamlining Form Module Code series, we created a dedicated Wrapper Class (OptFrame) for it.
For the other controls on the Form (ComboBox, ListBox, TextBox, and Command Button), only a single instance of each exists. Therefore, instead of creating separate Wrapper Classes, we declare them as single instances in the OptObject_Init Class Module, qualified with the WithEvents keyword.
These controls are then enabled with their required events, and their event subroutines are written directly in the intermediate class module (OptObject_Init), keeping the design lightweight and avoiding unnecessary Wrapper Classes.
Even though we have already created and used Wrapper Classes for these Objects earlier, using them in this case involves more VBA Code than necessary for a single instance of those Objects.
So, I created two Forms for Demo purposes:
frm_OptionGroup - All Control's Wrapper Classes are used in the OptObject_Init Class
frm_OptionGroup2 - Only Opt_Frame Wrapper Class is in the Opt_Object_Init2 Class.
The Opt_Object_Init2 Class Module Code.
The frm_OptionGroup2 Form's Intermediate Class Module (Opt_Object_Init2) Code is given below:
Option Compare Database
Option Explicit
Private WithEvents txt As Access.TextBox
Private WithEvents cmd As Access.CommandButton
Private WithEvents cbo As Access.ComboBox
Private WithEvents Lst As Access.ListBox
Private Fram As Opt_Frame2
Private iFrm As Access.Form
Private Coll As New Collection
'------------------------------------------------------
'Streamlining Form Module Code
'in Stand-alone Class Modules
'------------------------------------------------------
'Combo and Option Group Controls
'Author: a.p.r. pillai
'Date  : 31/08/2023
'Rights: All Rights(c) Reserved by www.msaccesstips.com
'------------------------------------------------------
'Form's Property GET/SET Procedures
Public Property Get m_Frm() As Form
    Set m_Frm = iFrm
End Property
Public Property Set m_Frm(ByRef mfrm As Form)
    Set iFrm = mfrm
    
    iFrm.cboEmp.DefaultValue = iFrm.cboEmp.Column(0, 1)
    iFrm.List0.Requery
    
    Set txt = iFrm.Result
    Set cmd = iFrm.cmdClose
    Set cbo = iFrm.cboEmp
    Set Lst = iFrm.List0
    
Call Class_Init
End Property
'Events Enabling Subroutine
Private Sub Class_Init()
Dim ctl As Control
Const EP = "[Event Procedure]"
'Scan for Form Controls
'and Enable the required Event Procedures
For Each ctl In iFrm.Controls 'Find TextBox, ComboBox & CommandButtons
    Select Case TypeName(ctl)
            Case "OptionGroup"
              Select Case ctl.Name
                Case "Frame7" 'Option Group Name
                    Set Fram = New Opt_Frame2 'Create Instance
                    Set Fram.opt_Frm = iFrm 'Assign Form Object
                    Set Fram.o_opt = ctl   'TextBox
                    
                        Fram.o_opt.OnClick = EP
                        
                    Coll.Add Fram 'Save EmpTextBox Class
                    Set Fram = Nothing 'Erase temp Instance
              End Select
        Case "CommandButton"
                   cmd.OnClick = EP
                    
        Case "ComboBox"
                   cbo.AfterUpdate = EP
                   cbo.OnGotFocus = EP
                   cbo.OnLostFocus = EP
          
        Case "TextBox"
            Select Case ctl.Name
                Case "Result"
                   txt.OnGotFocus = EP
                   txt.OnLostFocus = EP
            End Select
                    
        Case "ListBox"
                Lst.OnGotFocus = EP
                Lst.OnLostFocus = EP
                        
    End Select
Next
End Sub
Private Sub Class_Terminate()
'Delete Collection Object contents
    Do While Coll.Count > 0
        Coll.Remove 1
    Loop
    
    Set iFrm = Nothing
End Sub
'Event Subroutines
Private Sub txt_GotFocus()
        GFColor iFrm, txt 'Field Highlight
End Sub
Private Sub txt_LostFocus()
    LFColor iFrm, txt 'Field Highlight
End Sub
Private Sub cmd_Click()
    If MsgBox("Close " & iFrm.Name & " Form?", vbYesNo + vbQuestion, "cmd_Click") = vbYes Then
        DoCmd.Close acForm, iFrm.Name
        Exit Sub
    End If
End Sub
Private Sub cbo_GotFocus()
    GFColor iFrm, cbo 'ComboBox highlight
    
    'Reset OptionGroup to default settings
    iFrm.Frame7 = Null 'Reset earlier selection of OptionGroup option
    iFrm!lblResult.Caption = "Result"
    iFrm.Result.Value = 0
    
End Sub
Private Sub cbo_LostFocus()
    LFColor iFrm, cbo 'ComboBox highlight
End Sub
Private Sub cbo_AfterUpdate()
  iFrm.List0.Requery
  
End Sub
'Event Subroutines Code
Private Sub lst_GotFocus()
    GFColor iFrm, Lst 'ListBox highlight
End Sub
Private Sub lst_LostFocus()
    LFColor iFrm, Lst 'ListBox highlight
End Sub
Segmentwise Review of the VBA Code.
The Global Declaration Code segment is given below for review:
Option Compare Database Option Explicit Private WithEvents txt As Access.TextBox Private WithEvents cmd As Access.CommandButton Private WithEvents cbo As Access.ComboBox Private WithEvents Lst As Access.ListBox Private Fram As Opt_Frame2 Private iFrm As Access.Form Private Coll As New Collection
All single-instance control declarations are placed in the global area of the module, just as we did at the beginning of this tutorial series.
Since the OptionGroup Control is a new addition, its dedicated Wrapper Class is included here.
Following this, the Form and Collection Object declarations are defined. The Collection Object is required only for the OptionGroup Control (Frame7), as it manages its wrapper class instances.
The Property Procedure Segment.
Next, the iFrm's Property Procedure Code Segment is given below:
'Form's Property GET/SET Procedures
Public Property Get m_Frm() As Form
    Set m_Frm = iFrm
End Property
Public Property Set m_Frm(ByRef mfrm As Form)
    Set iFrm = mfrm
    
    'Set the ComboBox EmployeeID first item as default value
    iFrm.cboEmp.DefaultValue = iFrm.cboEmp.Column(0, 1)
    iFrm.List0.Requery 'Refresh the Order Details ListBox
    
    Set txt = iFrm.Result
    Set cmd = iFrm.cmdClose
    Set cbo = iFrm.cboEmp
    Set Lst = iFrm.List0
    
Call Class_Init
End Property
In the Set m_Frm() Property Procedure, the ComboBox and ListBox are initialized with their default values when the Form is opened.
After that, references for all the single-instance controls on the Form are assigned to the corresponding object variables declared in the global area. Finally, the Class_Init() Subroutine is called to complete the setup.
The Class_Init() Subroutine.
'Events Enabling Subroutine
Private Sub Class_Init()
Dim ctl As Control
Const EP = "[Event Procedure]"
'Scan for Form Controls
'and Enable the required Event Procedures
For Each ctl In iFrm.Controls 'Find TextBox, ComboBox & CommandButtons
    Select Case TypeName(ctl)
            Case "OptionGroup"
              Select Case ctl.Name
                Case "Frame7" 'Option Group Name
                    Set Fram = New Opt_Frame2 'Create Instance
                    Set Fram.opt_Frm = iFrm 'Assign Form Object
                    Set Fram.o_opt = ctl   'TextBox
                    
                        Fram.o_opt.OnClick = EP
                        
                    Coll.Add Fram 'Save EmpTextBox Class
                    Set Fram = Nothing 'Erase temp Instance
              End Select
        Case "CommandButton"
                   cmd.OnClick = EP
                    
        Case "ComboBox"
                   cbo.AfterUpdate = EP
                   cbo.OnGotFocus = EP
                   cbo.OnLostFocus = EP
          
        Case "TextBox"
            Select Case ctl.Name
                Case "Result"
                   txt.OnGotFocus = EP
                   txt.OnLostFocus = EP
            End Select
                   
        Case "ListBox"
                Lst.OnGotFocus = EP
                Lst.OnLostFocus = EP
                        
    End Select
Next
End Sub 
The Class_Init() Subroutine begins in the usual way by scanning the Form for its controls. When it identifies the OptionGroup control (Frame7), the Click Event is enabled, and the control is then added to the Collection Object.
The references for the other Form controls have already been assigned in the Set m_frm() Property Procedure. Their Events are also enabled at this stage, and the corresponding Event Subroutine code will be written directly in this Class Module.
In the case of the TextBox, there is another control named EID, which is kept hidden on the Form. Although hidden, it still appears during the scanning cycle and is enabled with Events. Since no Event Procedure code exists for this TextBox in the current Module, it has no impact on functionality. However, for clarity, we explicitly check for the specific Result TextBox and enable its Events, thereby ignoring the hidden EID TextBox. Following this, the ListBox is also enabled with the required Events.
The Event Subroutines of Single Control Instance Cases.
Next, the Event Subroutines Segment Code, which runs in the Opt_Object_Init2 Class.
'Event Runs automatically when the Form is Closed.
Private Sub Class_Terminate()
'Delete Collection Object contents
    Do While Coll.Count > 0
        Coll.Remove 1
    Loop
    
    Set iFrm = Nothing
End Sub
'TextBox Event Subroutines for highlighting the control
Private Sub txt_GotFocus()
        GFColor iFrm, txt 'Field Highlight
End Sub
Private Sub txt_LostFocus()
    LFColor iFrm, txt 'Field Highlight
End Sub
'Command Button Subroutines
Private Sub cmd_Click()
    If MsgBox("Close " & iFrm.Name & " Form?", vbYesNo + vbQuestion, "cmd_Click") = vbYes Then
        DoCmd.Close acForm, iFrm.Name
        Exit Sub
    End If
End Sub
'ComboBox Subroutines
Private Sub cbo_GotFocus()
    GFColor iFrm, cbo 'ComboBox highlight
    
    'Reset OptionGroup to default settings
    iFrm.Frame7 = Null 'Reset earlier selection of OptionGroup option
    iFrm!lblResult.Caption = "Result"
    iFrm.Result.Value = 0
    
End Sub
Private Sub cbo_LostFocus()
    LFColor iFrm, cbo 'ComboBox highlight
End Sub
Private Sub cbo_AfterUpdate()
  iFrm.List0.Requery
  
End Sub
'ListBox Event Subroutines Code
Private Sub lst_GotFocus()
    GFColor iFrm, Lst 'ListBox highlight
End Sub
Private Sub lst_LostFocus()
    LFColor iFrm, Lst 'ListBox highlight
End Sub
All Event Subroutines are written with the Object Name declared in the Global Declaration Area in the Opt_Object_Init2 Class Module.
Demo Database Download
Streamlining Form Module Code in Standalone Class Module.
- Reusing Form Module VBA Code for New Projects.
- Streamlining Form Module Code - Part Two.
- Streamlining Form Module Code - Part Three
- Streamlining Form Module Code - Part Four
- Streamlining Form Module Code - Part Five
- Streamlining Form Module Code - Part Six
- Streamlining Form Module Code - Part Seven
- Streamlining Form Module Code - Part Eight
- Streamlining Form Module Code - Part Nine
- Streamlining Form Module Code - Part Ten
- Streamlining Form Module Code - Part Eleven
- Streamlining Report Module Code in Class Module
- Streamlining Module Code Report Line Hiding-13.
- Streamlining Form Module Code Part-14.
- Streamlining Custom Made Form Wizard-15.
- Streamlining VBA Custom Made Report Wizard-16.
- Streamlining VBA External Files List in Hyperlinks-17
- Streamlining Events VBA 3D Text Wizard-18
- Streamlining Events VBA RGB Color Wizard-19
- Streamlining Events Numbers to Words-20
- Access Users Group(Europe) Presentation-21
- The Event Firing Mechanism of MS Access-22
- One TextBox and Three Wrapper Class Instances-23
- Streamlining Code Synchronized Floating Popup Form-24
- Streamlining Code Compacting/Repair Database-25
- Streamlining Code Remainder Popup Form-26
- Streamlining Code Editing Data in Zoom-in Control-27
- Streamlining Code Filter By Character and Sort-28
- Table Query Records in Collection Object-29
- Class for All Data Entry Editing Forms-30
- Wrapper Class Module Creation Wizard-31
- wrapper-class-template-wizard-v2








 Streamline11.zip
Streamline11.zip









 
 
 
