Skip to content

Commit

Permalink
Small changes for Mac-to-Windows compatibility
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Oct 24, 2014
1 parent f836331 commit ce93ede
Show file tree
Hide file tree
Showing 6 changed files with 59 additions and 35 deletions.
Binary file modified specs/Excel-REST - Specs - Async.xlsm
Binary file not shown.
Binary file modified specs/Excel-REST - Specs.xlsm
Binary file not shown.
2 changes: 1 addition & 1 deletion specs/OAuth1AuthenticatorSpecs.bas
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ Public Function Specs() As SpecSuite
Request.AddParameter "c", "Howdy!"
Request.AddQuerystringParam "d", 789

.Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy%21&d=789"
.Expect(Auth.RequestParameters(Client, Request)).ToEqual "a=123&b=456&c=Howdy!&d=789"
End With

With Specs.It("should handle spaces in parameters correctly")
Expand Down
15 changes: 8 additions & 7 deletions specs/RestHelpersSpecs.bas
Original file line number Diff line number Diff line change
Expand Up @@ -131,9 +131,10 @@ Public Function Specs() As SpecSuite
End With

With Specs.It("should url encode values")
.Expect(RestHelpers.UrlEncode(" !""#$%&'")).ToEqual "%20%21%22%23%24%25%26%27"
.Expect(RestHelpers.UrlEncode("$&+,/:;=?@", EncodeUnsafe:=False)).ToEqual "%24%26%2B%2C%2F%3A%3B%3D%3F%40"
.Expect(RestHelpers.UrlEncode(" ""<>#%{}|\^~[]`")).ToEqual "%20%22%3C%3E%23%25%7B%7D%7C%5C%5E%7E%5B%5D%60"
.Expect(RestHelpers.UrlEncode("A + B")).ToEqual "A%20%2B%20B"
.Expect(RestHelpers.UrlEncode("A + B", True)).ToEqual "A+%2B+B"
.Expect(RestHelpers.UrlEncode("A + B", SpaceAsPlus:=True)).ToEqual "A+%2B+B"
End With

With Specs.It("should decode url values")
Expand All @@ -157,7 +158,7 @@ Public Function Specs() As SpecSuite
B.Add "d & e", "A + B"

Encoded = RestHelpers.ConvertToUrlEncoded(RestHelpers.CombineObjects(A, B))
.Expect(Encoded).ToEqual "a=1&b=4.14&c=Howdy%21&d+%26+e=A+%2B+B"
.Expect(Encoded).ToEqual "a=1&b=4.14&c=Howdy!&d+%26+e=A+%2B+B"
End With

With Specs.It("should parse url-encoded string")
Expand Down Expand Up @@ -223,22 +224,22 @@ Public Function Specs() As SpecSuite
End With

With Specs.It("should extract parts from url")
Set Parts = RestHelpers.UrlParts("https://www.google.com/dir/1/2/search.html?message=Howdy World!&other=123#hash")
Set Parts = RestHelpers.UrlParts("https://www.google.com/dir/1/2/search.html?message=Howdy%20World!&other=123#hash")

.Expect(Parts("Protocol")).ToEqual "https"
.Expect(Parts("Host")).ToEqual "www.google.com"
.Expect(Parts("Port")).ToEqual "443"
.Expect(Parts("Path")).ToEqual "/dir/1/2/search.html"
.Expect(Parts("Querystring")).ToEqual "message=Howdy World!&other=123"
.Expect(Parts("Querystring")).ToEqual "message=Howdy%20World!&other=123"
.Expect(Parts("Hash")).ToEqual "hash"

Set Parts = RestHelpers.UrlParts("localhost:3000/dir/1/2/page%202.html?message=Howdy%20World%21&other=123#hash")
Set Parts = RestHelpers.UrlParts("localhost:3000/dir/1/2/page%202.html?message=Howdy%20World!&other=123#hash")

.Expect(Parts("Protocol")).ToEqual ""
.Expect(Parts("Host")).ToEqual "localhost"
.Expect(Parts("Port")).ToEqual "3000"
.Expect(Parts("Path")).ToEqual "/dir/1/2/page%202.html"
.Expect(Parts("Querystring")).ToEqual "message=Howdy%20World%21&other=123"
.Expect(Parts("Querystring")).ToEqual "message=Howdy%20World!&other=123"
.Expect(Parts("Hash")).ToEqual "hash"
End With

Expand Down
6 changes: 3 additions & 3 deletions specs/RestRequestSpecs.bas
Original file line number Diff line number Diff line change
Expand Up @@ -109,10 +109,10 @@ Public Function Specs() As SpecSuite
With Specs.It("should URL encode querystring")
Set Request = New RestRequest

Request.AddParameter "A B", " !""#$%&'"
Request.AddParameter "A B", "$&+,/:;=?@"
Request.Method = httpGET

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

With Specs.It("should use body string directly if no parameters")
Expand Down Expand Up @@ -257,7 +257,7 @@ Public Function Specs() As SpecSuite
.Expect(Request.Body).ToEqual "{""A"":123,""B"":""Howdy!""}"

Request.Format = formurlencoded
.Expect(Request.Body).ToEqual "A=123&B=Howdy%21"
.Expect(Request.Body).ToEqual "A=123&B=Howdy!"
End With

With Specs.It("should allow array/collection for body")
Expand Down
71 changes: 47 additions & 24 deletions src/RestHelpers.bas
Original file line number Diff line number Diff line change
Expand Up @@ -332,12 +332,14 @@ End Function

''
' Url encode the given string
' Reference: http://www.blooberry.com/indexdot/html/topics/urlencoding.htm
'
' @param {Variant} Text The raw string to encode
' @param {Boolean} [SpaceAsPlus = False] Use plus sign for encoded spaces (otherwise %20)
' @param {Boolean} [EncodeUnsafe = True] Encode unsafe characters
' @return {String} Encoded string
' --------------------------------------------- '
Public Function UrlEncode(Text As Variant, Optional SpaceAsPlus As Boolean = False) As String
Public Function UrlEncode(Text As Variant, Optional SpaceAsPlus As Boolean = False, Optional EncodeUnsafe As Boolean = True) As String
Dim UrlVal As String
Dim StringLen As Long

Expand All @@ -346,34 +348,39 @@ Public Function UrlEncode(Text As Variant, Optional SpaceAsPlus As Boolean = Fal

If StringLen > 0 Then
ReDim Result(StringLen) As String
Dim i As Long, charCode As Integer
Dim Char As String, space As String
Dim i As Long
Dim CharCode As Integer
Dim Char As String
Dim Space As String

' Set space value
If SpaceAsPlus Then
space = "+"
Space = "+"
Else
space = "%20"
Space = "%20"
End If

' Loop through string characters
For i = 1 To StringLen
' Get character and ascii code
Char = Mid$(UrlVal, i, 1)
charCode = Asc(Char)
Select Case charCode
Case 97 To 122, 65 To 90, 48 To 57, 45, 46, 95, 126
' Use original for AZaz09-._~
Result(i) = Char
Case 32
' Add space
Result(i) = space
Case 0 To 15
' Convert to hex w/ leading 0
Result(i) = "%0" & Hex(charCode)
CharCode = Asc(Char)

Select Case CharCode
Case 36, 38, 43, 44, 47, 58, 59, 61, 63, 64
' Reserved characters
Result(i) = "%" & Hex(CharCode)
Case 32, 34, 35, 37, 60, 62, 91 To 94, 96, 123 To 126
' Unsafe characters
If EncodeUnsafe Then
If CharCode = 32 Then
Result(i) = Space
Else
Result(i) = "%" & Hex(CharCode)
End If
End If
Case Else
' Convert to hex
Result(i) = "%" & Hex(charCode)
Result(i) = Char
End Select
Next i
UrlEncode = Join(Result, "")
Expand Down Expand Up @@ -533,18 +540,32 @@ Public Function UrlParts(Url As String) As Dictionary
"print ""Protocol="" . $url->scheme;" & vbNewLine & _
"print "" | Host="" . $url->host;" & vbNewLine & _
"print "" | Port="" . $url->port;" & vbNewLine & _
"print "" | Path="" . $url->path;" & vbNewLine & _
"print "" | Querystring="" . $url->query;" & vbNewLine & _
"print "" | FullPath="" . $url->full_path;" & vbNewLine & _
"print "" | Hash="" . $url->frag;" & vbNewLine & _
"}'"

Results = Split(ExecuteInShell(Command).Output, " | ")
For Each ResultPart In Results
EqualsIndex = InStr(1, ResultPart, "=")
Key = Trim(VBA.Mid$(ResultPart, 1, EqualsIndex - 1))
Value = Trim(VBA.Mid$(ResultPart, EqualsIndex + 1))

Parts.Add Key, Value
If Key = "FullPath" Then
' For properly escaped path and querystring, need to use full_path
' But, need to split FullPath into Path...?Querystring
Dim QueryIndex As Integer

QueryIndex = InStr(1, Value, "?")
If QueryIndex > 0 Then
Parts.Add "Path", Mid$(Value, 1, QueryIndex - 1)
Parts.Add "Querystring", Mid$(Value, QueryIndex + 1)
Else
Parts.Add "Path", Value
Parts.Add "Querystring", ""
End If
Else
Parts.Add Key, Value
End If
Next ResultPart

If AddedProtocol And Parts.Exists("Protocol") Then
Expand Down Expand Up @@ -792,7 +813,9 @@ Public Function CreateResponseFromCURL(Result As ShellResult, Optional Format As
Dim ErrorNumber As Long

ErrorNumber = Result.ExitCode / 256
If ErrorNumber = 28 Then
' 7 - CURLE_COULDNT_CONNECT
' 28 - CURLE_OPERATION_TIMEDOUT
If ErrorNumber = 7 Or ErrorNumber = 28 Then
Set CreateResponseFromCURL = CreateResponse(StatusCodes.RequestTimeout, "Request Timeout")
Else
LogError "cURL Error: " & ErrorNumber, "RestHelpers.CreateResponseFromCURL"
Expand Down Expand Up @@ -1151,7 +1174,7 @@ Public Function ExecuteInShell(Command As String) As ShellResult
End If

Do While feof(File) = 0
Chunk = VBA.space$(50)
Chunk = VBA.Space$(50)
Read = fread(Chunk, 1, Len(Chunk) - 1, File)
If Read > 0 Then
Chunk = VBA.Left$(Chunk, Read)
Expand Down

0 comments on commit ce93ede

Please sign in to comment.