Results 1 to 8 of 8

Thread: Control Array for VBA Controls

  1. #1

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,853

    Control Array for VBA Controls

    Okay, I don't do that much VBA coding, but I do write a substantial amount of VB6 code, and I'm frequently automating Word and/or Excel from VB6.

    However, when in the VBA, one thing that has often annoyed me is the lack of control arrays (which I use often in VB6). Therefore, and after watching the other recent thread in this forum named "Multi ComboBox", I decided to sketch out the following.

    I don't believe I'm allowed to actually attach an Excel file, so I'll give it to you in pieces. Also, there's not an Office Development CodeBank, so here it is.

    There are three pieces to this scheme for spoofing control arrays in the VBA:
    1. A class named "clsCboArray". That name is critical.
    2. A class named "clsTheCbo". That name is also critical.
    3. A UserForm1 to show how it all works. This could be any name. For this example, there are two comboboxes on it (SomeCombo001 & SomeCombo002).


    Also, as a note, when creating your "events" in some form (UserForm1 for this example), be sure they're declared as Public (and not even Friend), as that's necessary for the CallByName statement that's in the clsTheCbo to work correctly.

    Here's the code for the class named clsCboArray:
    Code:
    
    Option Explicit
    '
    Dim collEvts As New Collection
    Dim collCtls As New Collection
    Dim frmTheParent As IUnknown        ' Declaring as UserForm doesn't allow CallByName.
    Dim sTheBaseName As String
    '
    
    Friend Sub Setup(frmParent As UserForm, cboBaseName As String)
        '
        ' The whole idea here is to design a scheme whereby something close to Control Arrays will be allowed in the VBA.
        ' The idea is to give each control (of a certain type) a "base name" followed by three digits.  For example:
        '       cboSomeCombo001
        '       cboSomeCombo002
        '       cboSomeCombo003
        ' Notice that there MUST be three digits at the end for this to work correctly
        ' With those ComboBoxes on a VBA form, you'd just instantiate and then call this Setup procedure as follows:
        '
        '       Dim cboSomeCombo As New clsCboArray  ' <--- Placed at module level of some UserForm.
        '
        ' Note, to look most like a Control Array, it's best if the above object variable is named the same as the "base name" of the Control Array.
        '
        ' And then, in UserForm_Initialize, we'd do something like the following:
        '
        '       cboSomeCombo.Setup UserForm1, "cboSomeCombo"
        '
        ' And then, we can use it like a Control Array.  The only difference is that, when calling methods, the Index
        ' is part of the property, rather than part of the control.  For instance:
        '
        '       Debug.Print cboSomeCombo.Text(1)    ' Where 1 is the Index.
        '
        Dim ctl As Control
        Dim oTheCtl As clsTheCbo
        Dim Index As Integer
        '
        Set frmTheParent = frmParent
        sTheBaseName = cboBaseName
        '
        For Each ctl In frmParent.Controls                                                  ' Enumerate the controls on the form, finding the ones we want.
            If TypeName(ctl) = "ComboBox" Then                                              ' Make sure it's a ComboBox.
                If Left$(ctl.Name, Len(sTheBaseName)) = sTheBaseName Then                   ' Make sure it matches our "base name".
                    If Len(ctl.Name) = Len(sTheBaseName) + 3& Then                          ' Its name should be exactly three characters longer than the base name.
                        If Not Right$(ctl.Name, 3) Like "*[!0-9]*" Then                     ' And those three characters should all be numbers.
                            Index = Val(Right$(ctl.Name, 3))                                ' Make our index out of those three characters.
                            Set oTheCtl = New clsTheCbo                                     ' Create a new object to catch this control's events.
                            oTheCtl.SetCtlAndForm ctl, frmTheParent, cboBaseName, Index     ' Tell that object which control (and parent, and index) we're dealing with.
                            collEvts.Add oTheCtl, ctl.Name                                  ' Stuff this object into a collection so it stays instantiated beyond the life of this procedure.
                            collCtls.Add ctl, ctl.Name                                      ' Also save our control at this level so we can create methods and properties for it.
                        End If
                    End If
                End If
            End If
        Next ctl
    End Sub
    
    ' ***********************************************
    ' ***********************************************
    '
    ' Methods (Sub and Function).  Add whatever you'll be using, following the scheme shown.
    '
    ' ***********************************************
    ' ***********************************************
    
    Friend Sub AddItem(Index As Integer, Item As String, Optional varIndex As Integer = -1)
        If varIndex = -1 Then
            collCtls.Item(sTheBaseName & Format$(Index, "000")).AddItem Item
        Else
            collCtls.Item(sTheBaseName & Format$(Index, "000")).AddItem Item, varIndex
        End If
    End Sub
    
    Friend Sub RemoveItem(Index As Integer, RowToDelete As Integer) ' RowToDelete is ZERO based.
        collCtls.Item(sTheBaseName & Format$(Index, "000")).RemoveItem RowToDelete
    End Sub
    
    ' ***********************************************
    ' ***********************************************
    '
    ' Properties.  Add whatever you'll be using, following the scheme shown.
    '
    ' ***********************************************
    ' ***********************************************
    
    Friend Property Get Style(Index As Integer) As fmStyle
        Style = collCtls.Item(sTheBaseName & Format$(Index, "000")).Style
    End Property
    
    Friend Property Get Text(Index As Integer) As String
        Text = collCtls.Item(sTheBaseName & Format$(Index, "000")).Text
    End Property
    
    Friend Property Let Text(Index As Integer, NewText As String)
        collCtls.Item(sTheBaseName & Format$(Index, "000")).Text = NewText
    End Property
    
    And here's the code for the class named clsTheCbo:
    Code:
    
    Option Explicit
    '
    Dim WithEvents TheCtl As ComboBox
    Dim frmTheParent As IUnknown        ' Declaring as UserForm doesn't allow CallByName.
    Dim sTheBaseName As String
    Dim iTheIndex As Integer
    '
    
    Friend Sub SetCtlAndForm(ctl As ComboBox, frmParent As UserForm, cboBaseName As String, Index As Integer)
        '
        ' This entire class is intended to be used only with the clsCboArray class.
        '
        Set frmTheParent = frmParent
        sTheBaseName = cboBaseName
        Set TheCtl = ctl
        iTheIndex = Index
    End Sub
    
    ' ***********************************************
    ' ***********************************************
    '
    ' Events.  Add whatever you'll be using, following the scheme shown.
    '
    ' ***********************************************
    ' ***********************************************
    
    Private Sub TheCtl_Change()
        On Error Resume Next        ' On error used so that we're not required to have all the events in the parent form for the control array.
            CallByName frmTheParent, sTheBaseName & "_Change", VbMethod, iTheIndex
        On Error GoTo 0
    End Sub
    
    Private Sub TheCtl_Click()
        On Error Resume Next        ' On error used so that we're not required to have all the events in the parent form for the control array.
            CallByName frmTheParent, sTheBaseName & "_Click", VbMethod, iTheIndex
        On Error GoTo 0
    End Sub
    
    And lastly, a bit of code to test our UserForm1:
    Code:
    
    Option Explicit
    '
    Dim SomeCombo As New clsCboArray            ' Will be destroyed (along with all its children) when this form's code is destroyed.
    '
    
    Private Sub UserForm_Click()
        MsgBox SomeCombo.Text(1)
    End Sub
    
    Private Sub UserForm_Initialize()
        SomeCombo.Setup Me, "SomeCombo"         ' Now we can use our SomeCombo### controls like a control array, events and all.
    
        ' Put some data into the two ComboBoxes.
        SomeCombo.AddItem 1, "asdf"
        SomeCombo.AddItem 1, "qwer"
        SomeCombo.AddItem 2, "fghj"
        SomeCombo.AddItem 2, "rtyu"
    End Sub
    
    Public Sub SomeCombo_Change(Index As Integer)           ' A control array "like" event.
        Debug.Print "change, text: ", SomeCombo.Text(Index)
    End Sub
    
    Public Sub SomeCombo_Click(Index As Integer)            ' A control array "like" event.
        Debug.Print "click, text: ", SomeCombo.Text(Index)
    End Sub
    
    Now, I've also got two ComboBoxes on this UserForm1. They're named SomeCombo001 and SomeCombo002. That's critical for the test to work. I didn't set any special properties for them.

    Once that's all setup, I just executed the following code in the Immediate window for my test:

    Code:
    
    UserForm1.Show
    
    And voila, control arrays in the VBA.

    I didn't flesh out all the specific Properties, Methods, and Events. But that's rather easy once this framework is in place.

    Creating multiple instantiations of the clsCboArray at the top of a UserForm, it would be trivial to have multiple control arrays on a single form. And, following the same scheme, it'd be easy to have multiple forms with multiple control arrays.

    Also, this same framework could be easily adapted to the VBA TextBox or any of the other controls.

    Please be sure to read the comments in the code, particularly those in the Setup method of the clsCboArray module.

    Enjoy,
    Elroy

    EDIT1: I improved the comments in the clsCboArray module a bit, but no changes to the code.
    EDIT2: I liked the idea of using the Like statement (see following posts), so I made the change to use it. I also added another Method (RemoveItem) and Property (Style) just for grins.
    Last edited by Elroy; Apr 22nd, 2018 at 09:38 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  2. #2
    PowerPoster
    Join Date
    Dec 2004
    Posts
    25,618

    Re: Control Array for VBA Controls

    I don't believe I'm allowed to actually attach an Excel file,
    zip the workbook

    i just realized this was not a question, but a good example
    there are a few other examples in this forum, other example i have worked with have not used the call by name for the events, but passed them back to the control event, maybe not better, but different
    i do my best to test code works before i post it, but sometimes am unable to do so for some reason, and usually say so if this is the case.
    Note code snippets posted are just that and do not include error handling that is required in real world applications, but avoid On Error Resume Next

    dim all variables as required as often i have done so elsewhere in my code but only posted the relevant part

    come back and mark your original post as resolved if your problem is fixed
    pete

  3. #3
    PowerPoster Zvoni's Avatar
    Join Date
    Sep 2012
    Location
    To the moon and then left
    Posts
    4,418

    Re: Control Array for VBA Controls

    Nice!
    if you're not against API-calls, there is IMHO a way easier method for your IsAllNumbers-Function.
    Just take a look at the API/C-Function "strspn"
    if you're interested i could rewrite your function

    EDIT: After thinking about it, i'm pretty sure it's max 3 lines of code.
    wouldn't surprise if it's even only 2 lines
    Last edited by Zvoni; Tomorrow at 31:69 PM.
    ----------------------------------------------------------------------------------------

    One System to rule them all, One Code to find them,
    One IDE to bring them all, and to the Framework bind them,
    in the Land of Redmond, where the Windows lie
    ---------------------------------------------------------------------------------
    People call me crazy because i'm jumping out of perfectly fine airplanes.
    ---------------------------------------------------------------------------------
    Code is like a joke: If you have to explain it, it's bad

  4. #4
    Hyperactive Member
    Join Date
    Aug 2017
    Posts
    380

    Re: Control Array for VBA Controls

    Quote Originally Posted by Zvoni View Post
    if you're not against API-calls, there is IMHO a way easier method for your IsAllNumbers-Function.
    Just take a look at the API/C-Function "strspn"
    if you're interested i could rewrite your function

    EDIT: After thinking about it, i'm pretty sure it's max 3 lines of code.
    wouldn't surprise if it's even only 2 lines
    The Like operator can do it in only 1 line:

    Code:
    If Not Right$(ctl.Name, 3) Like "*[!0-9]*" Then
    Quote Originally Posted by Elroy View Post
    Code:
    
    Dim frmTheParent As IUnknown        ' Declaring as UserForm doesn't allow CallByName.
    
    I believe As Object would work as well.

  5. #5
    PowerPoster Zvoni's Avatar
    Join Date
    Sep 2012
    Location
    To the moon and then left
    Posts
    4,418

    Re: Control Array for VBA Controls

    Correct with the Like-Oprator, but with the API you don't have to define how many characters you're checking.
    It's one of my general purpose-functions i like to use together with its counterpart "strcspn"
    Last edited by Zvoni; Tomorrow at 31:69 PM.
    ----------------------------------------------------------------------------------------

    One System to rule them all, One Code to find them,
    One IDE to bring them all, and to the Framework bind them,
    in the Land of Redmond, where the Windows lie
    ---------------------------------------------------------------------------------
    People call me crazy because i'm jumping out of perfectly fine airplanes.
    ---------------------------------------------------------------------------------
    Code is like a joke: If you have to explain it, it's bad

  6. #6

    Thread Starter
    PowerPoster Elroy's Avatar
    Join Date
    Jun 2014
    Location
    Near Nashville TN
    Posts
    9,853

    Re: Control Array for VBA Controls

    Well, I like the Like operator (and it works out as a nice pun too).

    Personally, I'm not at all afraid of API calls, but I'm thinking many beginners may be splashing around in the Office VBA, and that's a jump in understanding. So I'm not crazy about adding that approach to what I've outlined. Although, I must admit that I did introduce some moderate-level concepts (Classes/Objects, Nesting of them, Collections, CallByName, Friend declarations). But hey ho, it is all part of the VBA core language.

    Y'all Take Care,
    Elroy

    EDIT1: Also, the moment we get into API calls, we get into all the PtrSafe, LongPtr, and LongLong stuff. Well, that is, if we're going to be VBA-32-bit and VBA-64-bit compatible. I believe everything I've done should work just fine on either.
    Last edited by Elroy; Apr 22nd, 2018 at 09:48 AM.
    Any software I post in these forums written by me is provided "AS IS" without warranty of any kind, expressed or implied, and permission is hereby granted, free of charge and without restriction, to any person obtaining a copy. To all, peace and happiness.

  7. #7
    New Member
    Join Date
    Jul 2022
    Location
    Knoxville, TN
    Posts
    1

    Re: Control Array for VBA Controls

    Elroy, I have always appreciated elegant solutions to complicated problems. Could you provide details on implementing mouse events. While it would be good to include all of the arguments, I am mainly interested in capturing the Index of the object. I am creating compact forms that benefit from using Labels to emulate CommandButtons. By losing the white space around the CommandButton caption, I can minimize the Form size. Alternately, if there is a way to minimize the white space on a CommandButton, this would be the best approach.

    Thanks for your contributions.

    Since my original post I have worked this out. I just needed to include the required parameters in methods. Here is the code for the mouse events

    Code:
    Private Sub TheCtl_MouseDown(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
        On Error Resume Next        ' On error used so that we're not required to have all the events in the parent form for the control array.
            CallByName frmTheParent, sTheBaseName & "_MouseDown", VbMethod, iTheIndex
        On Error GoTo 0
    End Sub
    
    Private Sub TheCtl_MouseUp(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
        On Error Resume Next        ' On error used so that we're not required to have all the events in the parent form for the control array.
            CallByName frmTheParent, sTheBaseName & "_MouseUp", VbMethod, iTheIndex
        On Error GoTo 0
    End Sub
    
    Private Sub TheCtl_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
        On Error Resume Next        ' On error used so that we're not required to have all the events in the parent form for the control array.
            CallByName frmTheParent, sTheBaseName & "_MouseMove", VbMethod, iTheIndex
        On Error GoTo 0
    End Sub
    Last edited by gwflew; Aug 17th, 2022 at 07:18 AM. Reason: Worked out the problem

  8. #8
    Lively Member
    Join Date
    May 2021
    Posts
    95

    Re: Control Array for VBA Controls

    Thank you for this - and, in particular, for the comments:

    Code:
    Dim frmTheParent As IUnknown        ' Declaring as UserForm doesn't allow CallByName.
    This, for example, has been extremely helpful.

    I've been undertaking a hobby project that converts VB6 Projects to VBA Projects - and Control Arrays have been one of the things that has caused me headaches. That - Forms v UserForms, lack of a Timer control, Resource Files, the PictureBox, an API bitness converter... it's a long list... which is further complicated by the fact that I don't have VB6, so a lot of it is guesswork.

    Your project above helps lighten the load! :-)

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •  



Click Here to Expand Forum to Full Width