Skip to content

Commit 1dbafac

Browse files
committed
Merge pull request #27 from timhall/formurlencoded
Add form-urlencoded
2 parents af2dc70 + 621d09f commit 1dbafac

File tree

5 files changed

+153
-46
lines changed

5 files changed

+153
-46
lines changed

specs/Excel-REST - Specs.xlsm

43.7 KB
Binary file not shown.

specs/RestHelpersSpecs.bas

Lines changed: 32 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,11 +18,12 @@ Public Function Specs() As SpecSuite
1818
Dim Parsed As Object
1919
Dim Obj As Object
2020
Dim Coll As Collection
21-
Dim A As Object
22-
Dim B As Object
23-
Dim Combined As Object
21+
Dim A As Dictionary
22+
Dim B As Dictionary
23+
Dim Combined As Dictionary
2424
Dim Whitelist As Variant
25-
Dim Filtered As Object
25+
Dim Filtered As Dictionary
26+
Dim Encoded As String
2627
Dim ResponseHeaders As String
2728
Dim Headers As Collection
2829
Dim Cookies As Dictionary
@@ -107,10 +108,14 @@ Public Function Specs() As SpecSuite
107108

108109
With Specs.It("should url encode values")
109110
.Expect(RestHelpers.URLEncode(" !""#$%&'")).ToEqual "%20%21%22%23%24%25%26%27"
111+
.Expect(RestHelpers.URLEncode("A + B")).ToEqual "A%20%2B%20B"
112+
.Expect(RestHelpers.URLEncode("A + B", True)).ToEqual "A+%2B+B"
110113
End With
111114

112115
With Specs.It("should decode url values")
113116
.Expect(RestHelpers.URLDecode("+%20%21%22%23%24%25%26%27")).ToEqual " !""#$%&'"
117+
.Expect(RestHelpers.URLDecode("A%20%2B%20B")).ToEqual "A + B"
118+
.Expect(RestHelpers.URLDecode("A+%2B+B")).ToEqual "A + B"
114119
End With
115120

116121
With Specs.It("should join url with /")
@@ -155,6 +160,29 @@ Public Function Specs() As SpecSuite
155160
.Expect(Filtered.Exists("dangerous")).ToEqual False
156161
End With
157162

163+
With Specs.It("should combine and convert parameters to url-encoded string")
164+
Set A = New Dictionary
165+
Set B = New Dictionary
166+
167+
A.Add "a", 1
168+
A.Add "b", 3.14
169+
B.Add "b", 4.14
170+
B.Add "c", "Howdy!"
171+
B.Add "d & e", "A + B"
172+
173+
Encoded = RestHelpers.DictionariesToUrlEncodedString(A, B)
174+
.Expect(Encoded).ToEqual "a=1&b=4.14&c=Howdy%21&d+%26+e=A+%2B+B"
175+
End With
176+
177+
With Specs.It("should parse url-encoded string")
178+
Set Parsed = RestHelpers.ParseUrlEncoded("a=1&b=3.14&c=Howdy%21&d+%26+e=A+%2B+B")
179+
180+
.Expect(Parsed("a")).ToEqual "1"
181+
.Expect(Parsed("b")).ToEqual "3.14"
182+
.Expect(Parsed("c")).ToEqual "Howdy!"
183+
.Expect(Parsed("d & e")).ToEqual "A + B"
184+
End With
185+
158186
With Specs.It("should extract headers from response headers")
159187
ResponseHeaders = "Connection: keep -alive" & vbCrLf & _
160188
"Date: Tue, 18 Feb 2014 15:00:26 GMT" & vbCrLf & _

specs/RestRequestSpecs.bas

Lines changed: 25 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@ Public Function Specs() As SpecSuite
9797
Request.AddParameter "A B", " !""#$%&'"
9898
Request.Method = httpGET
9999

100-
.Expect(Request.FormattedResource).ToEqual "?A%20B=%20%21%22%23%24%25%26%27"
100+
.Expect(Request.FormattedResource).ToEqual "?A+B=+%21%22%23%24%25%26%27"
101101
End With
102102

103103
With Specs.It("should include cachebreaker in FormattedResource by default")
@@ -144,7 +144,7 @@ Public Function Specs() As SpecSuite
144144
.Expect(Request.Body).ToEqual "{""A"":123}"
145145

146146
Request.Method = httpPOST
147-
.Expect(Request.Body).ToEqual "{""A"":123,""b"":456}"
147+
.Expect(Request.Body).ToEqual "{""b"":456,""A"":123}"
148148
End With
149149

150150
With Specs.It("should use given client base url for FullUrl only if BaseUrl isn't already set")
@@ -175,25 +175,20 @@ Public Function Specs() As SpecSuite
175175
.Expect(Request.FullUrl("facebook.com/api/")).ToEqual "https://facebook.com/api/status"
176176
End With
177177

178-
With Specs.It("should user form-urlencoded content type for non-GET requests with parameters")
178+
With Specs.It("should include content-type based on specified format")
179179
Set Request = New RestRequest
180180

181181
Request.AddParameter "A", 123
182182
Request.Method = httpPOST
183183

184-
.Expect(Request.ContentType).ToEqual "application/x-www-form-urlencoded;charset=UTF-8"
185-
End With
186-
187-
With Specs.It("should use application/json for GET requests with parameters and requests without parameters")
188-
Set Request = New RestRequest
189-
190-
Request.Method = httpPOST
184+
' JSON by default
191185
.Expect(Request.ContentType).ToEqual "application/json"
192186

193-
Request.AddParameter "A", 123
194-
Request.Method = httpGET
195-
187+
Request.Format = json
196188
.Expect(Request.ContentType).ToEqual "application/json"
189+
190+
Request.Format = formurlencoded
191+
.Expect(Request.ContentType).ToEqual "application/x-www-form-urlencoded;charset=UTF-8"
197192
End With
198193

199194
With Specs.It("should override existing headers, url segments, and parameters")
@@ -260,6 +255,23 @@ Public Function Specs() As SpecSuite
260255
.Expect(Request.Body).ToEqual "Howdy!"
261256
End With
262257

258+
With Specs.It("should format body based on set format")
259+
Set Request = New RestRequest
260+
Request.Method = httpPOST
261+
262+
Request.AddParameter "A", 123
263+
Request.AddParameter "B", "Howdy!"
264+
265+
' JSON by default
266+
.Expect(Request.Body).ToEqual "{""A"":123,""B"":""Howdy!""}"
267+
268+
Request.Format = json
269+
.Expect(Request.Body).ToEqual "{""A"":123,""B"":""Howdy!""}"
270+
271+
Request.Format = formurlencoded
272+
.Expect(Request.Body).ToEqual "A=123&B=Howdy%21"
273+
End With
274+
263275
InlineRunner.RunSuite Specs
264276
End Function
265277

src/RestHelpers.bas

Lines changed: 66 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -259,6 +259,69 @@ Public Function FilterObject(ByVal Original As Dictionary, Whitelist As Variant)
259259
Set FilterObject = Filtered
260260
End Function
261261

262+
''
263+
' Convert dictionaries to url encoded string
264+
'
265+
' @param {Dictionary...} Dictionaries
266+
' @return {String} UrlEncoded string (e.g. a=123&b=456&...)
267+
' --------------------------------------------- '
268+
269+
Public Function DictionariesToUrlEncodedString(ParamArray Dictionaries() As Variant) As String
270+
Dim Encoded As String
271+
Dim i As Integer
272+
Dim Combined As Dictionary
273+
Dim ParameterKey As Variant
274+
275+
Set Combined = Dictionaries(LBound(Dictionaries))
276+
For i = LBound(Dictionaries) + 1 To UBound(Dictionaries)
277+
Set Combined = CombineObjects(Combined, Dictionaries(i))
278+
Next i
279+
280+
If Not Combined Is Nothing Then
281+
For Each ParameterKey In Combined.keys()
282+
If Len(Encoded) > 0 Then: Encoded = Encoded & "&"
283+
Encoded = Encoded & URLEncode(ParameterKey, True) & "=" & URLEncode(Combined(ParameterKey), True)
284+
Next ParameterKey
285+
End If
286+
287+
DictionariesToUrlEncodedString = Encoded
288+
End Function
289+
290+
''
291+
' Parse url-encoded string to Dictionary
292+
'
293+
' @param {String} UrlEncoded
294+
' @return {Dictionary} Parsed
295+
' --------------------------------------------- '
296+
297+
Public Function ParseUrlEncoded(Encoded As String) As Dictionary
298+
Dim Items As Variant
299+
Dim i As Integer
300+
Dim Parts As Variant
301+
Dim Parsed As New Dictionary
302+
Dim Key As String
303+
Dim Value As Variant
304+
305+
Items = Split(Encoded, "&")
306+
For i = LBound(Items) To UBound(Items)
307+
Parts = Split(Items(i), "=")
308+
309+
If UBound(Parts) - LBound(Parts) >= 1 Then
310+
' TODO: Handle numbers, arrays, and object better here
311+
Key = URLDecode(CStr(Parts(LBound(Parts))))
312+
Value = URLDecode(CStr(Parts(LBound(Parts) + 1)))
313+
314+
If Parsed.Exists(Key) Then
315+
Parsed(Key) = Value
316+
Else
317+
Parsed.Add Key, Value
318+
End If
319+
End If
320+
Next i
321+
322+
Set ParseUrlEncoded = Parsed
323+
End Function
324+
262325
''
263326
' Prepare http request for execution
264327
'
@@ -415,7 +478,9 @@ Public Function CreateResponseFromHttp(ByRef Http As Object, Optional Format As
415478

416479
' Convert content to data by format
417480
Select Case Format
418-
Case Else
481+
Case AvailableFormats.formurlencoded
482+
Set CreateResponseFromHttp.Data = RestHelpers.ParseUrlEncoded(Http.ResponseText)
483+
Case AvailableFormats.json
419484
Set CreateResponseFromHttp.Data = RestHelpers.ParseJSON(Http.ResponseText)
420485
End Select
421486

src/RestRequest.cls

Lines changed: 30 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ Public Enum AvailableMethods
4949
End Enum
5050
Public Enum AvailableFormats
5151
json
52+
formurlencoded
5253
End Enum
5354

5455
' --------------------------------------------- '
@@ -108,7 +109,6 @@ End Property
108109

109110
Public Property Get FormattedResource() As String
110111
Dim segment As Variant
111-
Dim parameterKey As Variant
112112

113113
FormattedResource = Me.Resource
114114

@@ -131,45 +131,47 @@ Public Property Get FormattedResource() As String
131131
If (Me.Parameters.count > 0 And Me.Method = httpGET) Or Me.QuerystringParams.count > 0 Then
132132
If InStr(FormattedResource, "?") <= 0 Then
133133
FormattedResource = FormattedResource & "?"
134+
Else
135+
FormattedResource = FormattedResource & "&"
134136
End If
135137

136138
' Only load parameters to querystring if GET request (otherwise they are added to the body)
137139
If Me.Method = httpGET Then
138-
For Each parameterKey In Me.Parameters.keys()
139-
If Right(FormattedResource, 1) <> "?" Then: FormattedResource = FormattedResource & "&"
140-
FormattedResource = FormattedResource & URLEncode(parameterKey) & "=" & URLEncode(Me.Parameters(parameterKey))
141-
Next parameterKey
140+
FormattedResource = FormattedResource & RestHelpers.DictionariesToUrlEncodedString(Me.Parameters, Me.QuerystringParams)
141+
Else
142+
FormattedResource = FormattedResource & RestHelpers.DictionariesToUrlEncodedString(Me.QuerystringParams)
142143
End If
143-
144-
For Each parameterKey In Me.QuerystringParams.keys()
145-
If Right(FormattedResource, 1) <> "?" Then: FormattedResource = FormattedResource & "&"
146-
FormattedResource = FormattedResource & URLEncode(parameterKey) & "=" & URLEncode(Me.QuerystringParams(parameterKey))
147-
Next parameterKey
148144
End If
149145
End If
150146
End Property
151147

152148
Public Property Get Body() As String
153149
' Add body if it's defined or parameters have been set and it is not a GET request
154150
If Not pBody Is Nothing Or pBodyString <> "" Or (Me.Parameters.count > 0 And Me.Method <> httpGET) Then
155-
Select Case Me.Format
156-
' (Currently only JSON is supported)
157-
Case Else
158-
If pBodyString <> "" Then
159-
If Me.Parameters.count > 0 And Me.Method <> httpGET Then
160-
Err.Raise vbObjectError + 1, "RestRequest.Body", "Unable to combine body string and parameters"
151+
If pBodyString <> "" Then
152+
If Me.Parameters.count > 0 And Me.Method <> httpGET Then
153+
Err.Raise vbObjectError + 1, "RestRequest.Body", "Unable to combine body string and parameters"
154+
Else
155+
Body = pBodyString
156+
End If
157+
Else
158+
Select Case Me.Format
159+
Case AvailableFormats.formurlencoded
160+
If Me.Method <> httpGET Then
161+
' Combine defined body and parameters and convert to JSON
162+
Body = RestHelpers.DictionariesToUrlEncodedString(Me.Parameters, pBody)
161163
Else
162-
Body = pBodyString
164+
Body = RestHelpers.DictionariesToUrlEncodedString(pBody)
163165
End If
164-
Else
166+
Case AvailableFormats.json
165167
If Me.Method <> httpGET Then
166168
' Combine defined body and parameters and convert to JSON
167-
Body = RestHelpers.ConvertToJSON(CombineObjects(pBody, Me.Parameters))
169+
Body = RestHelpers.ConvertToJSON(CombineObjects(Me.Parameters, pBody))
168170
Else
169171
Body = RestHelpers.ConvertToJSON(pBody)
170172
End If
171-
End If
172-
End Select
173+
End Select
174+
End If
173175
End If
174176
End Property
175177

@@ -205,7 +207,9 @@ End Property
205207

206208
Public Property Get FormatName() As String
207209
Select Case Me.Format
208-
Case Else
210+
Case AvailableFormats.formurlencoded
211+
FormatName = "form-urlencoded"
212+
Case AvailableFormats.json
209213
FormatName = "json"
210214
End Select
211215
End Property
@@ -215,12 +219,10 @@ Public Property Get ContentType() As String
215219
ContentType = pContentType
216220
Else
217221
Select Case Me.Format
218-
Case Else
219-
If Me.Method <> httpGET And Me.Parameters.count > 0 Then
220-
ContentType = "application/x-www-form-urlencoded;charset=UTF-8"
221-
Else
222-
ContentType = "application/json"
223-
End If
222+
Case AvailableFormats.formurlencoded
223+
ContentType = "application/x-www-form-urlencoded;charset=UTF-8"
224+
Case AvailableFormats.json
225+
ContentType = "application/json"
224226
End Select
225227
End If
226228
End Property

0 commit comments

Comments
 (0)