Skip to content

Commit 563d8ab

Browse files
First content commit
1 parent dcbfab8 commit 563d8ab

39 files changed

+370
-2
lines changed

DirectoryManager.cls

Lines changed: 216 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,216 @@
1+
VERSION 1.0 CLASS
2+
BEGIN
3+
MultiUse = -1 'True
4+
END
5+
Attribute VB_Name = "DirectoryManager"
6+
Attribute VB_GlobalNameSpace = False
7+
Attribute VB_Creatable = False
8+
Attribute VB_PredeclaredId = False
9+
Attribute VB_Exposed = False
10+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
11+
'Version 1.0.0 '
12+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
13+
'MIT License '
14+
' '
15+
'Copyright (c) 2022 M. Scott Lassiter '
16+
' '
17+
'Permission is hereby granted, free of charge, to any person obtaining a copy '
18+
'of this software and associated documentation files (the "Software"), to deal '
19+
'in the Software without restriction, including without limitation the rights '
20+
'to use, copy, modify, merge, publish, distribute, sublicense, and/or sell '
21+
'copies of the Software, and to permit persons to whom the Software is '
22+
'furnished to do so, subject to the following conditions: '
23+
' '
24+
'The above copyright notice and this permission notice shall be included in all '
25+
'copies or substantial portions of the Software. '
26+
' '
27+
'THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR '
28+
'IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, '
29+
'FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE '
30+
'AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER '
31+
'LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, '
32+
'OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE '
33+
'SOFTWARE. '
34+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
35+
36+
Option Explicit
37+
38+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
39+
' Class Variables
40+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
41+
42+
Dim FolderPath As String
43+
Dim FolderName As String
44+
45+
Dim FoundFoldersList As New Collection
46+
Dim FoundFilesList As New Collection
47+
48+
Dim FoundFolders As New Collection
49+
Dim FoundFiles As New Collection
50+
51+
Dim isFile As Boolean
52+
Dim OmittedPrefixValue As String
53+
54+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
55+
' Properties
56+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
57+
58+
Public Property Get Path() As String
59+
Path = FolderPath
60+
End Property
61+
Public Property Let Path(PathName As String)
62+
'This is the entry point to initialize the class. Trying to use any feature before running this script should abort.
63+
FolderPath = PathName
64+
If Not (Exists) Then Exit Property
65+
FolderPath = FormatFilePath(FolderPath)
66+
67+
'Reinitialize if the same DirectoryManager class is set to a new path
68+
Set FoundFoldersList = New Collection
69+
Set FoundFilesList = New Collection
70+
Set FoundFolders = New Collection
71+
Set FoundFiles = New Collection
72+
73+
FindFilesAndFolders
74+
FindSubFilesAndFolders
75+
End Property
76+
77+
78+
Public Property Get Name() As String
79+
If isFile Then
80+
Name = Split(FolderPath, "\")(UBound(Split(FolderPath, "\")))
81+
Else
82+
Name = Split(FolderPath, "\")(UBound(Split(FolderPath, "\")) - 1)
83+
End If
84+
End Property
85+
86+
87+
Public Property Get Folders() As Collection
88+
Set Folders = FoundFolders
89+
End Property
90+
91+
92+
Public Property Get Files() As Collection
93+
Set Files = FoundFiles
94+
End Property
95+
96+
97+
Public Property Get Exists() As Boolean
98+
'Uninitialized instances of the class and folders that do not exist return false
99+
100+
On Error Resume Next
101+
If Len(Dir(FolderPath, vbDirectory)) = 0 Or FolderPath = "" Or Err <> 0 Then 'Gives error 52 if file name is invalid
102+
Exists = False
103+
Else
104+
Exists = True
105+
End If
106+
On Error GoTo 0
107+
108+
End Property
109+
110+
111+
Public Property Let OmittedPrefix(Omit As String)
112+
'If true, the DirectoryManager ignores all files and folders that begin with the specified characters.
113+
' This allows the end user to setup a file structure with folders or files that he or she does not want
114+
' to be included when the DirectoryManager scans a path.
115+
OmittedPrefixValue = Omit
116+
Path = FolderPath 'Reinitialize the DirectoryManager, this time using the new omit prefix
117+
End Property
118+
Public Property Get OmittedPrefix() As String
119+
OmittedPrefix = OmittedPrefixValue
120+
End Property
121+
122+
123+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
124+
' Functions and Methods
125+
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
126+
127+
Private Sub FindFilesAndFolders()
128+
'Loops through all files and folders in this path directory and adds them to their respective collections
129+
130+
Dim RefFolders As Variant
131+
Dim newItem As DirectoryManager
132+
133+
RefFolders = Dir(FolderPath, vbDirectory)
134+
Do While RefFolders <> "" And isFile = False
135+
136+
'Ignore the special folders '.' and '..'
137+
If RefFolders <> "." And RefFolders <> ".." Then
138+
If Left(RefFolders, Len(OmittedPrefixValue)) <> OmittedPrefixValue Or OmittedPrefixValue = "" Then 'Ignore the omitted prefixes, if specified
139+
If (GetAttr(FolderPath & RefFolders) And vbDirectory) = vbDirectory Then
140+
FoundFoldersList.Add RefFolders, RefFolders
141+
Else
142+
FoundFilesList.Add RefFolders, RefFolders
143+
End If
144+
End If
145+
End If
146+
147+
RefFolders = Dir 'Required to move to the next file
148+
Loop
149+
150+
End Sub
151+
152+
153+
Private Sub FindSubFilesAndFolders()
154+
'After the list of folders is identified, this function recursively creates a new Folder class for each folder
155+
' and repeats the process.
156+
Dim item As Variant
157+
Dim newFolder As DirectoryManager
158+
159+
160+
161+
For Each item In FoundFoldersList
162+
Set newFolder = New DirectoryManager
163+
newFolder.OmittedPrefix = OmittedPrefixValue
164+
newFolder.Path = FolderPath & item
165+
166+
InsertCollectionValueAlphabetically FoundFolders, newFolder, newFolder.Name
167+
Next item
168+
169+
For Each item In FoundFilesList
170+
Set newFolder = New DirectoryManager
171+
newFolder.OmittedPrefix = OmittedPrefixValue
172+
newFolder.Path = FolderPath & item
173+
174+
InsertCollectionValueAlphabetically FoundFiles, newFolder, newFolder.Name
175+
Next item
176+
177+
End Sub
178+
179+
180+
Private Sub InsertCollectionValueAlphabetically(Col As Collection, item As Variant, Key As String)
181+
'Collections do not have a built in sort feature. This loops through each item in the collection,
182+
' and once the new item (key) comes later than the current loop value (Col(i).Name), then it
183+
' immediately exits the loop and adds the Key into that spot.
184+
185+
Dim i As Long
186+
If Col.Count = 0 Then
187+
Col.Add item, Key 'First value gets added without trying to loop through
188+
Exit Sub
189+
End If
190+
191+
For i = 1 To Col.Count
192+
'Convert to lower case to get predictable behavior during ASCII text comparison
193+
If (LCase(Key) < LCase(Col(i).Name)) Then Exit For
194+
Next i
195+
196+
If i = 1 Then
197+
'Trying to add after index 0 results in an error
198+
Col.Add item, Key, 1
199+
Else
200+
Col.Add item, Key, , i - 1
201+
End If
202+
End Sub
203+
204+
205+
Private Function FormatFilePath(InputPath As String) As String
206+
'If a folder, normalize the root directory file path to have a backslash at the end of it.
207+
' Otherwise, it is a file and should be left alone.
208+
FormatFilePath = InputPath
209+
If (GetAttr(InputPath) And vbDirectory) = vbDirectory Then
210+
isFile = False
211+
If Right(InputPath, 1) <> "\" Then FormatFilePath = InputPath & "\"
212+
ElseIf Len(Dir(InputPath, vbReadOnly Or vbHidden Or vbSystem Or vbDirectory)) > 0 Then
213+
isFile = True
214+
End If
215+
216+
End Function

ExampleWorkbook.xlsm

26 KB
Binary file not shown.

README.md

Lines changed: 154 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,154 @@
1-
# Excel-VBA-Folder-Manager
2-
Manage files and folders in VBA without using FileSystemObject or setting special references.
1+
# Excel-VBA-Directory-Manager
2+
Uses a single Class to parse all the files and folders in a specified directory without using FileSystemObject or setting special references. Perfect for integrating into projects you can distribute to the lay person without worrying if they have set their references correctly in the VBA editor.
3+
4+
## Requirements
5+
- Microsoft Office 2007 or newer (Not tested for earlier versions)
6+
- A macro enabled file
7+
- Knowledge of how to [add a Class module](https://analystcave.com/vba-vba-class-tutorial/) to your project
8+
9+
## Getting Started
10+
A single Class file contains all functionality. To use it in your project, use one of the following methods to add them in the IDE:
11+
12+
To use it in your project, then use one of the following methods to add them in the IDE.
13+
14+
- Save the [source code module](/DirectoryManager.cls) to your machine, then import it into the Project using the IDE
15+
16+
Or,
17+
18+
- Create a blank class module in your project, name it `DirectoryManager`, and then copy/paste the [source code](/DirectoryManager.cls).
19+
20+
21+
# Class Properties
22+
23+
| Property | Type | Description |
24+
|--------------- |------------------------ |-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- |
25+
| Exists | Boolean (Read Only) | For both files and folders, returns `True` if the `Path` exists and is not an empty string. |
26+
| Files | Collection (Read Only) | Returns an Excel Collection object. Each item inside contains another instance of DirectoryManager for the applicable file. |
27+
| Folders | Collection (Read Only) | Returns an Excel Collection object. Each item inside contains another instance of DirectoryManager for the applicable folder. |
28+
| Name | String (Read Only) | Returns the name of the file or folder. |
29+
| OmittedPrefix | String (Read/Write) | Defaults to an empty string. If set, this will omit all files and folders that start with the `OmittedPrefix` string during the file parsing process. Changing this value will cause the `DirectoryManager` instance to recalculate. This value passes down to all files and folders beneath it. |
30+
| Path | String (Read/Write) | Returns the full system path of the file or folder. |
31+
32+
33+
34+
# Example Use
35+
36+
The below examples are also located in the [example workbook](/ExampleWorkbook.xlsm).
37+
38+
## Initial Setup
39+
40+
```VBA
41+
Sub CreateNewDirectoryManager()
42+
43+
Dim dm As DirectoryManager
44+
Dim item As Variant
45+
46+
Set dm = New DirectoryManager
47+
dm.Path = ThisWorkbook.Path & "\Sample Data Set"
48+
49+
'Print a list of all folders:
50+
Debug.Print "Folders: " & dm.Folders.Count
51+
For Each item In dm.Folders
52+
Debug.Print item.Name
53+
Next item
54+
55+
'Print a list of all files:
56+
Debug.Print "Files: " & dm.Files.Count
57+
For Each item In dm.Files
58+
Debug.Print item.Name
59+
Next item
60+
61+
'Output from above:
62+
63+
' Folders: 5
64+
' _My Personal Documents
65+
' Contacts
66+
' Documents
67+
' My Publications
68+
' Pictures
69+
' Files: 4
70+
' _Sample File A.txt
71+
' Sample File 1.txt
72+
' Sample File 2.txt
73+
' Sample File 3.txt
74+
75+
End Sub
76+
```
77+
78+
## Use Omitted Characters to Exclude Files or Folders
79+
Setting the `OmittedPrefix` property to a non-empty string will cause the DirectoryManager to exclude any file or folder that starts with that string.
80+
81+
```VBA
82+
Sub SetOmmitedPrefix()
83+
84+
Dim dm As DirectoryManager
85+
Dim item As Variant
86+
87+
Set dm = New DirectoryManager
88+
dm.OmittedPrefix = "_"
89+
dm.Path = ThisWorkbook.Path & "\Sample Data Set"
90+
91+
'Print a list of all folders:
92+
Debug.Print "Folders: " & dm.Folders.Count
93+
For Each item In dm.Folders
94+
Debug.Print item.Name
95+
Next item
96+
97+
'Print a list of all files:
98+
Debug.Print "Files: " & dm.Files.Count
99+
For Each item In dm.Files
100+
Debug.Print item.Name
101+
Next item
102+
103+
'Output from above:
104+
105+
' Folders: 4
106+
' Contacts
107+
' Documents
108+
' My Publications
109+
' Pictures
110+
' Files: 3
111+
' Sample File 1.txt
112+
' Sample File 2.txt
113+
' Sample File 3.txt
114+
115+
End Sub
116+
```
117+
Changing `OmittedPrefix` will cause the DirectoryManager to re-parse the file or folder set at the current `Path`.
118+
119+
## Check if a File or Folder Exists
120+
121+
The DirectoryManager can easily tell you if a file or folder at the specified `Path` exists.
122+
123+
```VBA
124+
Sub CheckIfFileOrFolderExists()
125+
126+
Dim dm As DirectoryManager
127+
128+
'Folders
129+
Set dm = New DirectoryManager
130+
dm.Path = ThisWorkbook.Path & "\Sample Data Set\Contacts"
131+
132+
Debug.Print dm.Exists 'True
133+
134+
dm.Path = ThisWorkbook.Path & "\Sample Data Set\Folder That Doesn't Exist"
135+
Debug.Print dm.Exists 'False
136+
137+
138+
'Files
139+
dm.Path = ThisWorkbook.Path & "\Sample Data Set\Contacts\My Phone.txt"
140+
Debug.Print dm.Exists 'True
141+
142+
dm.Path = ThisWorkbook.Path & "\Sample Data Set\Contacts\A File That Doesn't Exist.txt"
143+
Debug.Print dm.Exists 'False
144+
145+
End Sub
146+
```
147+
148+
149+
# License
150+
Distributed under the MIT License. See [LICENSE](./LICENSE) for more information.
151+
152+
153+
# Contact
154+
Reach me on [LinkedIn](https://www.linkedin.com/in/mscottlassiter/) or [Twitter](https://twitter.com/MScottLassiter).

Sample Data Set/Contacts/Business Contacts/Contact 1.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 2.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 3.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 4.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 5.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 6.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/Contact 7.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/_Contact 1A.txt

Whitespace-only changes.

Sample Data Set/Contacts/Business Contacts/_Contact 2A.txt

Whitespace-only changes.

Sample Data Set/Contacts/My Phone.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Emergency Contacts/Father.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Emergency Contacts/Mother.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Emergency Contacts/Sibling.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Emergency Contacts/Spouse.txt

Whitespace-only changes.

Sample Data Set/Contacts/_My Old Phone.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Personal Contacts/Contact 1.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Personal Contacts/Contact 2.txt

Whitespace-only changes.

Sample Data Set/Contacts/_Personal Contacts/Contact 3.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 1.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 2.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 3.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 4.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 5.txt

Whitespace-only changes.

Sample Data Set/Documents/Document 6.txt

Whitespace-only changes.

Sample Data Set/My Publications/Publication 1.txt

Whitespace-only changes.

Sample Data Set/My Publications/Publication 2.txt

Whitespace-only changes.

Sample Data Set/My Publications/Publication 3.txt

Whitespace-only changes.

Sample Data Set/My Publications/Publication 4.txt

Whitespace-only changes.

Sample Data Set/My Publications/Publication 5.txt

Whitespace-only changes.

Sample Data Set/Sample File 1.txt

Whitespace-only changes.

Sample Data Set/Sample File 2.txt

Whitespace-only changes.

Sample Data Set/Sample File 3.txt

Whitespace-only changes.

Sample Data Set/_My Personal Documents/Document 1.txt

Whitespace-only changes.

Sample Data Set/_My Personal Documents/Document 2.txt

Whitespace-only changes.

Sample Data Set/_My Personal Documents/Document 3.txt

Whitespace-only changes.

Sample Data Set/_Sample File A.txt

Whitespace-only changes.

0 commit comments

Comments
 (0)