7
\$\begingroup\$

Currently Rubberduck VBA files all the VBProject VBComponents in that do not have a Folder Annotation in a Folder named after the VBProject. It can be time consuming to manually organize the components for the first time and a inconvenient to add annotations to every Worksheet, Userform, Class, ...ect. When ran my code will organize any unfiled component by ProjectName.ComponentType.

Before

Rubberduck Code Explorer - No Folders

After

Rubberduck Code Explorer - With Default Folder Annotations

You will need to add a reference to the Microsoft Visual Basic for Applications Extensibility 5.3 and from file options check "Trust access to VBA project object model".

Programmatic Access

Private Sub AddDefaultFolderAnnotationsToVBComponents()
    Dim Component As VBComponent
    Dim Project As VBProject
    
    Select Case Application.Name
    Case "Microsoft Access", "Microsoft Word"
        Set Project = IIf(True, Application, 0).VBE.ActiveVBProject
            
    Case "Microsoft Excel"
        Set Project = IIf(True, Application, 0).ActiveWorkbook.VBProject

    Case "Microsoft PowerPoint"
        Set Project = IIf(True, Application, 0).VBE.VBProjects(1)
        
    End Select
    
    Dim FolderName As String
    Dim HasFolder As Boolean
    
    For Each Component In Project.VBComponents
        With Component.CodeModule
            If .CountOfLines = 0 Then
                HasFolder = False
            Else
                HasFolder = InStr(.Lines(1, .CountOfLines), Chr(39) & "@Folder")
            End If
        End With
        
        If Not HasFolder Then
            Select Case Component.Type
                Case vbext_ComponentType.vbext_ct_StdModule
                    FolderName = Project.Name & ".Modules"
                Case vbext_ComponentType.vbext_ct_ClassModule
                    FolderName = Project.Name & ".Classes"
                Case vbext_ComponentType.vbext_ct_MSForm
                    FolderName = Project.Name & ".Forms"
                Case vbext_ComponentType.vbext_ct_ActiveXDesigner
                    FolderName = Project.Name & ".Designers"
                Case vbext_ComponentType.vbext_ct_Document
                    FolderName = Project.Name & ".Documents"
            End Select
            
            Component.CodeModule.InsertLines 1, Chr(39) & "@Folder(""" & FolderName & """)"
        End If
    Next
End Sub

Note: I purposely kept all the functionality in a single procedure for portability.

Kudos to the Rubberduck team the latest version Rubberduck VBA v2.5 is a C# WPF that follows the MVVM pattern to the letter!

\$\endgroup\$
1
  • 1
    \$\begingroup\$ Comments are not for extended discussion; this conversation has been moved to chat. \$\endgroup\$ Commented Aug 20, 2020 at 2:17

1 Answer 1

7
\$\begingroup\$
HasFolder = InStr(.Lines(1, .CountOfLines), Chr(39) & "@Folder")

That condition can technically be True in modules that don't actually have the annotation; a @Folder Rubberduck annotation is only valid in a module's declarations section, so there's no need to grab the module content any further than .CountOfDeclarationLines - if the module is nearing the 10K lines capacity, using this instead of .CountOfLines could make a significant difference in the size of the string being passed to the InStr function.

Select Case Component.Type
    Case vbext_ComponentType.vbext_ct_StdModule
        FolderName = Project.Name & ".Modules"
    Case vbext_ComponentType.vbext_ct_ClassModule
        FolderName = Project.Name & ".Classes"
    Case vbext_ComponentType.vbext_ct_MSForm
        FolderName = Project.Name & ".Forms"
    Case vbext_ComponentType.vbext_ct_ActiveXDesigner
        FolderName = Project.Name & ".Designers"
    Case vbext_ComponentType.vbext_ct_Document
        FolderName = Project.Name & ".Documents"
End Select

I wouldn't repeat the concatenation here - just work out the last part of the name per the component type, and then concatenate with Project.Name & "." (I'd pull the separator dot out of the Case blocks as well) - and then I might give it a bit of breathing room, but that's more subjective:

    Select Case Component.Type
        Case vbext_ComponentType.vbext_ct_StdModule
            ChildFolderName = "Modules"

        Case vbext_ComponentType.vbext_ct_ClassModule
            ChildFolderName = "Classes"

        Case vbext_ComponentType.vbext_ct_MSForm
            ChildFolderName = "Forms"

        Case vbext_ComponentType.vbext_ct_ActiveXDesigner
            ChildFolderName = "Designers" 'note: not supported in VBA

        Case vbext_ComponentType.vbext_ct_Document
            ChildFolderName = "Documents"

    End Select
    FolderName = Project.Name & "." & ChildFolderName

I like the @Folder("Parent.Child") syntax and I see that's what you're generating here:

Component.CodeModule.InsertLines 1, Chr(39) & "@Folder(""" & FolderName & """)"

Note that this would also be legal... and simpler to generate:

Component.CodeModule.InsertLines 1, "'@Folder " & FolderName

Obviously if you prefer the parenthesized syntax (either works, it's really just down to personal preference) like I do then by all means keep it, but Rubberduck's new Move to Folder command doesn't put the parentheses in. I'd probably have the single-quote ' character spelled out, too, but I can see how a ' might be harder than necessary to read in the middle of a bunch of " double quotes. On the other hand, defining a constant for it would remove the need to have the "@Folder string literal defined in multiple places:

Private Const RD_FOLDER_ANNOTATION As String = "'@Folder "

...

Component.CodeModule.InsertLines 1, RD_FOLDER_ANNOTATION & FolderName

I have to mention that Rubberduck deliberately shoves all modules under the same default named-after-the-project folder (they can easily be sorted by component type in the Code Explorer), because we strongly believe grouping modules by component type is utterly useless and counter-productive: when I look at the code for a given functionality, I want to see all the code related to that functionality - and I couldn't care less about the component type of the code I'm looking at... it's mostly all class modules anyway.

A sane way to organize the modules in a project, is by functionality: you want your ThingView user form in the same place as your ThingModel class and your ThingPresenter and the Things custom collection - that way when you're working on that Thing, you don't have to dig up the various pieces in an ever-growing list of components under some useless "Class Modules" folder.

\$\endgroup\$
10
  • \$\begingroup\$ I really like the ChildFolderName, the extra white-space really cleans up the Select Case. I didn't not realize the parenthesis were optional. Chr(39) is the module that the AddDefaultFolderAnnotationsToVBComponents is in will not be skipped. \$\endgroup\$
    – TinMan
    Commented Aug 22, 2020 at 16:58
  • \$\begingroup\$ I disagree about categorizing by type being useless. This is how MVC Bootstraps folder structure are typically organized Project, Project.Views, Project-Models, Project.Controllers. Recommended Websites layout are usually structured by Root, Root.Css, Root.JS,Root.Php...etc. Having a default filing system also makes it easier to re-organize your folders because you will not have all the documents without code-behind cluttering up the place. A drop down to change folder views would go along way to making your point \$\endgroup\$
    – TinMan
    Commented Aug 22, 2020 at 17:36
  • 1
    \$\begingroup\$ Eureka! Only checking the declaration portion would eliminate the need for Chr(39)!! \$\endgroup\$
    – TinMan
    Commented Aug 22, 2020 at 17:38
  • 1
    \$\begingroup\$ Multiple folder annotations would result in... source files showing up in multiple places in the code explorer? How should we handle this? As for MVC default namespaces/folders, it's not the same thing at all because namespaces may or may not match/follow the folder structure (although it would be recommended that they do), ...and there is no distinct folders for Classes, Interfaces, Enums, Structs, Delegates, ...nor should there be any! You'll also find various blog posts about whether the default MVC project structure is useful... \$\endgroup\$ Commented Aug 22, 2020 at 18:05
  • 1
    \$\begingroup\$ @TinMan Peilonrayz is correct - including the updated code in the OP makes it kind of implicitly feel like the case is closed and no other input would be considered; that's why we encourage you to put the updated version in a new/follow-up "question" if you want additional feedback on the updated code. Basically we're all about the review and what good comes out of it - often the "final" result is never quite final anyway, ..for many of us anyway ;-) \$\endgroup\$ Commented Aug 22, 2020 at 18:33

Not the answer you're looking for? Browse other questions tagged or ask your own question.