Search code examples
excelvbacheckboxcomboboxuserform

userform loop for hiding and unhiding through multiple sequences


So i have this string of code... It is in a userform and is all vba based (IE not pulling data from a spreadsheet.)

Private Sub CHECK1_Click()

If CHECK1.value = False Then
    COMBO1.visible = False
        Else
            COMBO1.visible = True
    End If
End Sub

It works for perfectly for exactly one checkbox and combobox pair, I need it to work on all 61 on of them, individually... Being new to this I looked at case select possability but it looks like i would have to spell in out.

the userform is called "ORDER1"

All of the check boxes are named "CHECK1" THROUGH "CHECK61"

They all correspond to the combobox' aptly named "COMBO1" THROUGH "COMBO61"

(CHECK1=COMBO1 throguh the entire form.)

How can I make this work without putting 61 'click' events into the code? oh and I'm on excel 2010


Solution

  • In the comments there's already a "control array" with WithEvents as a possible solution, below I'll show another solution without the WithEvents:

    Copy this code to Notepad and save it as CatchEvents.cls

    VERSION 1.0 CLASS
    BEGIN
      MultiUse = -1  'True
    END
    Attribute VB_Name = "CatchEvents"
    Attribute VB_GlobalNameSpace = False
    Attribute VB_Creatable = False
    Attribute VB_PredeclaredId = False
    Attribute VB_Exposed = False
    Private Type GUID
          Data1 As Long
          Data2 As Integer
          Data3 As Integer
          Data4(0 To 7) As Byte
    End Type
    
    #If VBA7 And Win64 Then
          Private Declare PtrSafe Function ConnectToConnectionPoint Lib "shlwapi" Alias "#168" (ByVal punk As stdole.IUnknown, _
                  ByRef riidEvent As GUID, ByVal fConnect As Long, ByVal punkTarget As stdole.IUnknown, ByRef pdwCookie As Long, _
                  Optional ByVal ppcpOut As LongPtr) As Long
    #Else
         Private Declare Function ConnectToConnectionPoint Lib "shlwapi" Alias "#168" (ByVal punk As stdole.IUnknown, ByRef riidEvent As GUID, _
                  ByVal fConnect As Long, ByVal punkTarget As stdole.IUnknown, ByRef pdwCookie As Long, Optional ByVal ppcpOut As Long) As Long
    #End If
    
    'All Other Control-Events also possible
    'No need to use WithEvents
    'No need to put every Type of control in seperate collection or array, each event will fire no matter which control,
    'so in the eventcode controls can be separated from others
    'you can give your controls additional properties
    'Arguments as Cancel, KeyCode, KeyAscii , Button , x and Y still can be used
    
    Private EventGuide As GUID
    Private Ck As Long
    Private ctl As Object
    Private CustomProp As String
    
    Public Sub MyListClick()
    Attribute MyListClick.VB_UserMemId = -610
    If TypeName(ctl) = "CheckBox" Then
    ctl.Parent.Controls(Replace(ctl.Name, "CHECK", "COMBO")).Visible = ctl.Value
    End If
    End Sub
    
    Public Sub ConnectAllEvents(ByVal Connect As Boolean)
          With EventGuide
              .Data1 = &H20400
              .Data4(0) = &HC0
              .Data4(7) = &H46
          End With
          ConnectToConnectionPoint Me, EventGuide, Connect, ctl, Ck, 0&
    End Sub
    
    Public Property Let Item(Ctrl As Object)
          Set ctl = Ctrl
          Call ConnectAllEvents(True)
    End Property
    
    Public Sub Clear()
          If (Ck <> 0) Then Call ConnectAllEvents(False)
          Set ctl = Nothing
    End Sub
    

    In the VBA-editor right click somewhere on your Project and choose Import file, a Class named CatchEvents will now be in your Class Modules.

    Finally paste code below behind your Userform:

    Private AllControls() As New CatchEvents    
    
    Private Sub UserForm_Initialize()
    Dim j As Long
    ReDim AllControls(Controls.Count - 1)
        For j = 0 To Controls.Count - 1
             AllControls(j).Item = Controls(j)
        Next
    End Sub
    
    Private Sub UserForm_Terminate()
    Dim j As Long
      For j = LBound(AllControls) To UBound(AllControls)
              AllControls(j).Clear
          Next j
          Erase AllControls
    End Sub