Skip to content

Commit 4d352f2

Browse files
committed
Merge pull request #116 from VBA-tools/digest-updates
Fix extract header bug in DigestAuthenticator
2 parents 5812583 + 319edd8 commit 4d352f2

File tree

2 files changed

+28
-35
lines changed

2 files changed

+28
-35
lines changed

authenticators/DigestAuthenticator.cls

Lines changed: 26 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -158,38 +158,34 @@ End Function
158158
' @param {WebResponse} Response
159159
''
160160
Public Sub ExtractAuthenticateInformation(Response As WebResponse)
161-
Dim auth_Header As Dictionary
162-
For Each auth_Header In Response.Headers
163-
' Find authentication header
164-
If auth_Header("key") = "WWW-Authenticate" Then
165-
' Make sure using Digest authentication
166-
If VBA.Left$(auth_Header("value"), 6) = "Digest" Then
167-
Dim auth_Lines As Variant
168-
auth_Lines = VBA.Split(VBA.Mid$(auth_Header("value"), 7), vbCrLf)
169-
170-
Dim auth_i As Integer
171-
Dim auth_Key As String
172-
Dim auth_Value As String
173-
For auth_i = LBound(auth_Lines) To UBound(auth_Lines)
174-
auth_Key = VBA.LCase$(VBA.Trim$(VBA.Mid$(auth_Lines(auth_i), 1, VBA.InStr(1, auth_Lines(auth_i), "=") - 1)))
175-
auth_Value = VBA.Trim$(VBA.Mid$(auth_Lines(auth_i), VBA.InStr(1, auth_Lines(auth_i), "=") + 1, VBA.Len(auth_Lines(auth_i))))
176-
177-
' Remove quotes and trailing comma
178-
auth_Value = VBA.Replace(auth_Value, """", "")
179-
If VBA.Right$(auth_Value, 1) = "," Then auth_Value = VBA.Left$(auth_Value, VBA.Len(auth_Value) - 1)
180-
181-
' Find realm, nonce, and opaque
182-
If auth_Key = "realm" Then Me.Realm = auth_Value
183-
If auth_Key = "nonce" Then Me.ServerNonce = auth_Value
184-
If auth_Key = "opaque" Then Me.Opaque = auth_Value
185-
Next auth_i
186-
187-
WebHelpers.LogDebug "realm=" & Me.Realm & ", nonce=" & Me.ServerNonce & ", opaque=" & Me.Opaque, "DigestAuthenticator.ExtractAuthenticateInformation"
161+
Dim auth_Header As String
162+
auth_Header = WebHelpers.FindInKeyValues(Response.Headers, "WWW-Authenticate")
163+
164+
If auth_Header <> "" And VBA.Left$(auth_Header, 6) = "Digest" Then
165+
Dim auth_Lines As Variant
166+
auth_Lines = VBA.Split(VBA.Mid$(auth_Header, 7), vbCrLf)
167+
168+
Dim auth_i As Integer
169+
Dim auth_Key As String
170+
Dim auth_Value As String
171+
For auth_i = LBound(auth_Lines) To UBound(auth_Lines)
172+
auth_Key = VBA.LCase$(VBA.Trim$(VBA.Mid$(auth_Lines(auth_i), 1, VBA.InStr(1, auth_Lines(auth_i), "=") - 1)))
173+
auth_Value = VBA.Trim$(VBA.Mid$(auth_Lines(auth_i), VBA.InStr(1, auth_Lines(auth_i), "=") + 1, VBA.Len(auth_Lines(auth_i))))
174+
175+
' Remove quotes and trailing comma
176+
auth_Value = VBA.Replace(auth_Value, """", "")
177+
If VBA.Right$(auth_Value, 1) = "," Then
178+
auth_Value = VBA.Left$(auth_Value, VBA.Len(auth_Value) - 1)
188179
End If
189180

190-
Exit Sub
191-
End If
192-
Next auth_Header
181+
' Find realm, nonce, and opaque
182+
If auth_Key = "realm" Then Me.Realm = auth_Value
183+
If auth_Key = "nonce" Then Me.ServerNonce = auth_Value
184+
If auth_Key = "opaque" Then Me.Opaque = auth_Value
185+
Next auth_i
186+
187+
WebHelpers.LogDebug "realm=" & Me.Realm & ", nonce=" & Me.ServerNonce & ", opaque=" & Me.Opaque, "DigestAuthenticator.ExtractAuthenticateInformation"
188+
End If
193189
End Sub
194190

195191
' ============================================= '

specs/Specs_DigestAuthenticator.bas

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -54,13 +54,10 @@ Public Function Specs() As SpecSuite
5454
Dim Unauthorized As New WebResponse
5555
Unauthorized.StatusCode = 401
5656

57-
Dim UnauthorizedHeader As New Dictionary
58-
UnauthorizedHeader.Add "key", "WWW-Authenticate"
59-
UnauthorizedHeader.Add "value", "Digest realm=""[email protected]""," & vbCrLf & _
57+
Unauthorized.Headers.Add WebHelpers.CreateKeyValue("WWW-Authenticate", "Digest realm=""[email protected]""," & vbCrLf & _
6058
"qop=""auth,auth-int""," & vbCrLf & _
6159
"nonce=""dcd98b7102dd2f0e8b11d0f600bfb0c093""," & vbCrLf & _
62-
"Opaque = ""5ccc069c403ebaf9f0171e9517f40e41"""
63-
Unauthorized.Headers.Add UnauthorizedHeader
60+
"Opaque = ""5ccc069c403ebaf9f0171e9517f40e41""")
6461

6562
Auth.Realm = ""
6663
Auth.ServerNonce = ""

0 commit comments

Comments
 (0)