@@ -158,38 +158,34 @@ End Function
158
158
' @param {WebResponse} Response
159
159
''
160
160
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 )
188
179
End If
189
180
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
193
189
End Sub
194
190
195
191
' ============================================= '
0 commit comments