11Attribute VB_Name = "Credentials"
2- Private Const CredentialsPath As String = "..\credentials.txt"
32Private pCredentials As Dictionary
43
4+ Public Property Get CredentialsPath() As String
5+ ' Go up one folder from workbook path
6+ Dim Parts() As String
7+ Dim i As Long
8+ Parts = VBA.Split(ThisWorkbook.Path, Application.PathSeparator)
9+ For i = LBound(Parts) To UBound(Parts) - 1
10+ If CredentialsPath = "" Then
11+ CredentialsPath = CredentialsPath & Parts(i)
12+ Else
13+ CredentialsPath = CredentialsPath & Application.PathSeparator & Parts(i)
14+ End If
15+ Next i
16+
17+ CredentialsPath = CredentialsPath & Application.PathSeparator & "credentials.txt"
18+ End Property
19+
520Public Property Get Values() As Dictionary
621 If pCredentials Is Nothing Then
722 Set pCredentials = Load
@@ -12,7 +27,6 @@ End Property
1227Public Property Get Loaded() As Boolean
1328 Loaded = Not Values Is Nothing
1429End Property
15-
1630
1731Function Load () As Dictionary
1832 Dim Line As String
@@ -22,28 +36,29 @@ Function Load() As Dictionary
2236 Dim Value As String
2337
2438 Set pCredentials = New Dictionary
25- Open FullPath( CredentialsPath) For Input As #1
39+ Open CredentialsPath For Input As #1
2640
2741 On Error GoTo ErrorHandling
28- Do While Not EOF(1 )
42+ Do While Not VBA. EOF(1 )
2943 Line Input #1 , Line
44+ Line = VBA.Replace(Line, vbNewLine, "" )
3045
3146 ' Skip blank lines and comment lines
32- If Line <> "" And Left(Line, 1 ) <> "#" Then
33- If Left(Line, 1 ) = "-" Then
34- Line = Right(Line, Len(Line) - 1 )
35- Parts = Split(Line, ":" )
47+ If Line <> "" And VBA. Left$ (Line, 1 ) <> "#" Then
48+ If VBA. Left$ (Line, 1 ) = "-" Then
49+ Line = VBA. Right$ (Line, VBA. Len(Line) - 1 )
50+ Parts = VBA. Split(Line, ":" , 2 )
3651
3752 If UBound(Parts) >= 1 And Header <> "" And pCredentials.Exists(Header) Then
38- Key = Trim(Parts(0 ))
39- Value = Trim(Split(Parts(1 ), "#" )(0 ))
53+ Key = VBA. Trim(Parts(0 ))
54+ Value = VBA. Trim(Split(Parts(1 ), "#" )(0 ))
4055
4156 If Key <> "" And Value <> "" Then
4257 pCredentials(Header).Add Key, Value
4358 End If
4459 End If
4560 Else
46- Header = Trim(Split(Line, "#" )(0 ))
61+ Header = VBA. Trim(VBA. Split(Line, "#" )(0 ))
4762
4863 If Header <> "" Then
4964 pCredentials.Add Header, New Dictionary
@@ -57,7 +72,3 @@ Function Load() As Dictionary
5772ErrorHandling:
5873 Close #1
5974End Function
60-
61- Private Function FullPath (RelativePath As String ) As String
62- FullPath = ThisWorkbook.Path & "\" & RelativePath
63- End Function
0 commit comments