Whenever you have to interact with users there is information you would like to store outsie the lifetime of an application in order for it to be available at next startup.
The below class can assist in writing and reading property files into hidden temp directories like AppData in Windows systems. This way you can for example store user settings without having to deal with protecting and hiding Excel sheets. I think it is bad style to store information that only rarely is touched by a user in a workbook, which is used to process data. Unless Excel is not used as an interface to configure a lot of different parameters in an application, I use property files.
However the main advantage is that you can use a Scripting.Dictionary internally in the below class in order to ease getting and setting properties by name. This includes the following advantages compared to storing information in Excel files.
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
Option Explicit
' @Description - A collection holding property and key combinations. Keys are unique.
Private prop As Scripting.Dictionary
' @Description - A String holding the message of the last occured error.
Private lastErr As String
' @Description - A String holding the standard separator for writing tab delimited text
' files in order to store proprties in a temporary file on users machine.
Private Const sep As String = vbTab
' @Author - Alexander Bolte
' @Change Date - 2013-12-28
' @Description - Sets an existing property or adds a new property.
' @Param propName - A String working as a key, describing what the property value is.
' @Param propValue - A String holding the value of a property.
' @Returns - True, if setting or adding a property was successful, false otherwise.
Public Function setProp(ByVal propName As String, ByVal propValue As String) As Boolean
Dim ret As Boolean
On Error GoTo errHandle:
If prop.Exists(propName) Then
prop.Remove propName
End If
prop.Add propName, propValue
ret = prop.Exists(propName)
errHandle:
If Err.Number <> 0 Then
Err.Clear
End If
setProp = ret
End Function
' @Author - Alexander Bolte
' @Change Date - 2013-12-27
' @Description - Checks a properties existance in this collection object.
' @Param propName - A unique key string identifying a property.
' @Returns - True, if a property value is stored for the provided key string, false otheriwse.
Public Function isPropExisting(ByVal propName As String) As Boolean
Dim ret As Boolean
ret = prop.Exists(propName)
isPropExisting = ret
End Function
' @Author - Alexander Bolte
' @Change Date - 2013-12-27
' @Description - Returns a property value associated with the provided key string 'propName'.
' @Param propName - A key String, uniquely identifying a property.
' @Returns - A String, holding the value associated with the provided key string.
Public Function getProp(ByVal propName As String) As String
Dim ret As String
If prop.Exists(propName) Then
ret = prop(propName)
End If
getProp = ret
End Function
' @Author - Alexander Bolte
' @Change Date - 2013-12-28
' @Description - Writes the current property collection into a text file under provided file path.
' If a file with same full path already exists, it will be overwritten.
' One pair of key and value will be written in one line of the text file.
' Key / Identifier and value will be separated using tabulator character.
' @Param filePath - A String holding the path where the file should be written including file name and file type.
' @Returns - True, if writing the properties file succeeded, false otherwise.
Public Function writeProperties(ByVal filePath As String) As Boolean
Dim fileNum As Integer
Dim ret As Boolean
Dim keyArr() As Variant
Dim i As Integer
On Error GoTo errHandle:
fileNum = FreeFile()
keyArr = prop.Keys
' If file already exists, it will be overwritten.
If Dir(filePath) <> "" Then
Kill filePath
End If
Open filePath For Output As #fileNum
For i = LBound(keyArr) To UBound(keyArr)
Write #fileNum, keyArr(i) & sep & prop(keyArr(i))
Next i
ret = True
errHandle:
If Err.Number <> 0 Then
lastErr = Err.Number & " - " & Err.description
Err.Clear
End If
Close #fileNum
writeProperties = ret
End Function
' @Author - Alexander Bolte
' @Change Date - 2013-12-28
' @Description - Splits provided string using tabulator. The result is a pair of property key and value, which will then be added to the current collection.
' @Param newProp - A String holding a property key as well as the corresponding value, separated by tabulator.
' @Returns - True, if adding the new property pair succeeded, false otherwise.
Private Function addPropertyPair(ByVal newProp As String) As Boolean
Dim ret As Boolean
Dim propPair() As String
On Error GoTo errHandle:
newProp = Replace(newProp, """", "")
propPair = Split(newProp, sep)
If (UBound(propPair) > 0) Then
ret = Not prop.Exists(propPair(0))
If ret Then
prop.Add propPair(0), propPair(1)
End If
End If
errHandle:
If Err.Number <> 0 Then
Err.Clear
ret = False
End If
addPropertyPair = ret
End Function
' @Author - Alexander Bolte
' @Change Date - 2013-12-29
' @Description - Reads a tab separated properties text file available under provided file path.
' First column in text file has to provide the key string, uniquely identifying a property.
' Second column has to provide a value associated with a property. Can also be an empty string.
' @Param filePath - A file path to the properties file, which should be imported.
' @Returns - True, if reading the file succeeded, false otherwise. Will also indicate failure, if adding a duplicate property key.
Public Function readProperties(ByVal filePath As String) As Boolean
Dim fileNum As Integer
Dim newLine As String
Dim ret As Boolean
On Error GoTo errHandle:
If Dir(filePath) <> "" Then
ret = True
fileNum = FreeFile()
Open filePath For Input As #fileNum
While Not EOF(fileNum)
Line Input #fileNum, newLine
If newLine <> "" Then
If addPropertyPair(newLine) = False Then
ret = False
End If
End If
Wend
End If
errHandle:
If Err.Number <> 0 Then
lastErr = Err.Number & " - " & Err.description
Err.Clear
ret = False
End If
Close #fileNum
readProperties = ret
End Function
' @Author - Alexander Bolte
' @Description - In order to provide an additional information about errors occured during processing properties
' like I/O operations, this function returns always the message of the last error occured.
' @Returns - A String holding the last message of the last occured error. An empty string, if no error occured.
Public Function getLastError() As String
getLastError = lastErr
End Function
Private Sub Class_Initialize()
Set prop = New Scripting.Dictionary
End Sub
Private Sub Class_Terminate()
Set prop = Nothing
lastErr = ""
End Sub