Skip to content

Commit

Permalink
Fix UrlEncode edge cases
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Mar 4, 2016
1 parent 4685fa9 commit 918536d
Show file tree
Hide file tree
Showing 3 changed files with 36 additions and 13 deletions.
5 changes: 3 additions & 2 deletions specs/Specs_WebHelpers.bas
Original file line number Diff line number Diff line change
Expand Up @@ -194,9 +194,10 @@ Public Function Specs() As SpecSuite
' UrlEncode
' --------------------------------------------- '
With Specs.It("should url-encode string (with space as plus and encode unsafe options)")
.Expect(WebHelpers.UrlEncode("$&+,/:;=?@", EncodeUnsafe:=False)).ToEqual "%24%26%2B%2C%2F%3A%3B%3D%3F%40"
.Expect(WebHelpers.UrlEncode("ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz1234567890$-_.+!*'(),")).ToEqual "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz1234567890$-_.+!*'(),"
.Expect(WebHelpers.UrlEncode("&/:;=?@")).ToEqual "%26%2F%3A%3B%3D%3F%40"
.Expect(WebHelpers.UrlEncode(" ""<>#%{}|\^~[]`")).ToEqual "%20%22%3C%3E%23%25%7B%7D%7C%5C%5E%7E%5B%5D%60"
.Expect(WebHelpers.UrlEncode("A + B")).ToEqual "A%20%2B%20B"
.Expect(WebHelpers.UrlEncode("A + B")).ToEqual "A%20+%20B"
.Expect(WebHelpers.UrlEncode("A + B", SpaceAsPlus:=True)).ToEqual "A+%2B+B"
End With

Expand Down
8 changes: 4 additions & 4 deletions specs/Specs_WebRequest.bas
Original file line number Diff line number Diff line change
Expand Up @@ -228,9 +228,9 @@ Public Function Specs() As SpecSuite
Set Request = New WebRequest

Request.Resource = "{segment}"
Request.AddUrlSegment "segment", "$&+,/:;=?@"
Request.AddUrlSegment "segment", "&/:;=?@"

.Expect(Request.FormattedResource).ToEqual "%24%26%2B%2C%2F%3A%3B%3D%3F%40"
.Expect(Request.FormattedResource).ToEqual "%26%2F%3A%3B%3D%3F%40"
End With

With Specs.It("FormattedResource should include querystring parameters")
Expand Down Expand Up @@ -266,9 +266,9 @@ Public Function Specs() As SpecSuite
With Specs.It("FormattedResource should URL encode querystring")
Set Request = New WebRequest

Request.AddQuerystringParam "A B", "$&+,/:;=?@"
Request.AddQuerystringParam "A B", "&/:;=?@"

.Expect(Request.FormattedResource).ToEqual "?A+B=%24%26%2B%2C%2F%3A%3B%3D%3F%40"
.Expect(Request.FormattedResource).ToEqual "?A+B=%26%2F%3A%3B%3D%3F%40"
End With

' UserAgent
Expand Down
36 changes: 29 additions & 7 deletions src/WebHelpers.bas
Original file line number Diff line number Diff line change
Expand Up @@ -812,7 +812,14 @@ End Function

''
' Encode string for URLs
' Reference: http://www.blooberry.com/indexdot/html/topics/urlencoding.htm
' Reference:
' - http://www.blooberry.com/indexdot/html/topics/urlencoding.htm
' - https://www.ietf.org/rfc/rfc1738.txt
'
' From RFC 1738:
' > Thus, only alphanumerics, the special characters "$-_.+!*'(),", and
' reserved characters used for their reserved purposes may be used
' unencoded within a URL.
'
' @method UrlEncode
' @param {Variant} Text Text to encode
Expand Down Expand Up @@ -850,19 +857,34 @@ Public Function UrlEncode(Text As Variant, Optional SpaceAsPlus As Boolean = Fal
web_CharCode = VBA.Asc(web_Char)

Select Case web_CharCode
Case 97 To 122, 65 To 90, 48 To 57, 45, 46, 95, 126
Case 33, 36, 39, 40, 41, 42, 44, 45, 46, 48 To 57, 65 To 90, 95, 97 To 122
' Unencoded:
' alphanumeric - 48-57, 65-90, 97-122
' $-_.!*'(), - 33, 36, 39, 40, 41, 42, 43, 44, 45, 46, 95
web_Result(web_i) = web_Char
Case 32
web_Result(web_i) = web_Space
Case 0 To 15
web_Result(web_i) = "%0" & VBA.Hex(web_CharCode)
Case 34, 35, 37, 60, 62, 91 To 94, 96, 123 To 126
' Unsafe characters
' Unsafe characters: <>"#%{}|\^~[]`
If EncodeUnsafe Then
web_Result(web_i) = "%" & VBA.Hex(web_CharCode)
Else
web_Result(web_i) = web_Char
End If
Case 32
If EncodeUnsafe Then
web_Result(web_i) = web_Space
Else
web_Result(web_i) = web_Char
End If
Case 43
' + is considered safe special character
' but in space-as-plus cases, it's encoded to differentiate with space
If EncodeUnsafe And SpaceAsPlus Then
web_Result(web_i) = "%" & VBA.Hex(web_CharCode)
Else
web_Result(web_i) = web_Char
End If
Case 0 To 15
web_Result(web_i) = "%0" & VBA.Hex(web_CharCode)
Case Else
web_Result(web_i) = "%" & VBA.Hex(web_CharCode)
End Select
Expand Down

0 comments on commit 918536d

Please sign in to comment.