Skip to content

Commit df710e6

Browse files
committed
Merge pull request #151 from VBA-tools/url-decode-cookies
Improve cookie decoding
2 parents 29f450c + 228b0d7 commit df710e6

File tree

3 files changed

+25
-3
lines changed

3 files changed

+25
-3
lines changed

specs/Specs_WebResponse.bas

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -245,6 +245,20 @@ Public Function Specs() As SpecSuite
245245
.Expect(WebHelpers.FindInKeyValues(Cookies, "unsigned-cookie")).ToEqual "simple-cookie"
246246
End With
247247

248+
With Specs.It("should use RFC 6265 for decoding cookies")
249+
Set Response = New WebResponse
250+
ResponseHeaders = "Set-Cookie: a=plus+plus" & vbCrLf & _
251+
"Set-Cookie: b=""quotes""" & vbCrLf & _
252+
"Set-Cookie: c=semi-colon; Path=/"
253+
254+
Set Headers = Response.ExtractHeaders(ResponseHeaders)
255+
Set Cookies = Response.ExtractCookies(Headers)
256+
257+
.Expect(WebHelpers.FindInKeyValues(Cookies, "a")).ToEqual "plus+plus"
258+
.Expect(WebHelpers.FindInKeyValues(Cookies, "b")).ToEqual "quotes"
259+
.Expect(WebHelpers.FindInKeyValues(Cookies, "c")).ToEqual "semi-colon"
260+
End With
261+
248262
' ============================================= '
249263
' Errors
250264
' ============================================= '

src/WebHelpers.bas

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -853,9 +853,11 @@ End Function
853853
'
854854
' @method UrlDecode
855855
' @param {String} Encoded Text to decode
856+
' @param {Boolean} [PlusAsSpace = True] Decode plus as space
857+
' DEPRECATED: Default = True to align with existing behavior, will be changed to False in v5
856858
' @return {String} Decoded string
857859
''
858-
Public Function UrlDecode(Encoded As String) As String
860+
Public Function UrlDecode(Encoded As String, Optional PlusAsSpace As Boolean = True) As String
859861
Dim web_StringLen As Long
860862
web_StringLen = VBA.Len(Encoded)
861863

@@ -867,7 +869,7 @@ Public Function UrlDecode(Encoded As String) As String
867869
For web_i = 1 To web_StringLen
868870
web_Temp = VBA.Mid$(Encoded, web_i, 1)
869871

870-
If web_Temp = "+" Then
872+
If web_Temp = "+" And PlusAsSpace Then
871873
web_Temp = " "
872874
ElseIf web_Temp = "%" And web_StringLen >= web_i + 2 Then
873875
web_Temp = VBA.Mid$(Encoded, web_i + 1, 2)

src/WebResponse.cls

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -273,11 +273,17 @@ Public Function ExtractCookies(Headers As Collection) As Collection
273273
web_Key = VBA.Mid$(web_Cookie, 1, VBA.InStr(1, web_Cookie, "=") - 1)
274274
web_Value = VBA.Mid$(web_Cookie, VBA.InStr(1, web_Cookie, "=") + 1, VBA.Len(web_Cookie))
275275

276+
' Ignore text after semi-colon
276277
If VBA.InStr(1, web_Value, ";") > 0 Then
277278
web_Value = VBA.Mid$(web_Value, 1, VBA.InStr(1, web_Value, ";") - 1)
278279
End If
279280

280-
web_Cookies.Add WebHelpers.CreateKeyValue(web_Key, WebHelpers.UrlDecode(web_Value))
281+
' Ignore surrounding quotes
282+
If VBA.Left$(web_Value, 1) = """" Then
283+
web_Value = VBA.Mid$(web_Value, 2, VBA.Len(web_Value) - 2)
284+
End If
285+
286+
web_Cookies.Add WebHelpers.CreateKeyValue(web_Key, WebHelpers.UrlDecode(web_Value, PlusAsSpace:=False))
281287
Else
282288
WebHelpers.LogWarning _
283289
"Unrecognized cookie format: " & web_Cookie, "WebResponse.ExtractCookies"

0 commit comments

Comments
 (0)