Skip to content

Commit f1c4b9d

Browse files
committed
Add form-urlencoded format
1 parent 7263eb8 commit f1c4b9d

File tree

2 files changed

+65
-21
lines changed

2 files changed

+65
-21
lines changed

src/RestHelpers.bas

Lines changed: 39 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -274,7 +274,7 @@ Public Function DictionariesToUrlEncodedString(ParamArray Dictionaries() As Vari
274274

275275
Set Combined = Dictionaries(LBound(Dictionaries))
276276
For i = LBound(Dictionaries) + 1 To UBound(Dictionaries)
277-
Set Combined = CombineObjects(Combined, Dictionaries(i), False)
277+
Set Combined = CombineObjects(Combined, Dictionaries(i))
278278
Next i
279279

280280
If Not Combined Is Nothing Then
@@ -287,6 +287,41 @@ Public Function DictionariesToUrlEncodedString(ParamArray Dictionaries() As Vari
287287
DictionariesToUrlEncodedString = Encoded
288288
End Function
289289

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+
290325
''
291326
' Prepare http request for execution
292327
'
@@ -443,7 +478,9 @@ Public Function CreateResponseFromHttp(ByRef Http As Object, Optional Format As
443478

444479
' Convert content to data by format
445480
Select Case Format
446-
Case Else
481+
Case AvailableFormats.formurlencoded
482+
Set CreateResponseFromHttp.Data = RestHelpers.ParseUrlEncoded(Http.ResponseText)
483+
Case AvailableFormats.json
447484
Set CreateResponseFromHttp.Data = RestHelpers.ParseJSON(Http.ResponseText)
448485
End Select
449486

src/RestRequest.cls

Lines changed: 26 additions & 19 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
' --------------------------------------------- '
@@ -136,7 +137,7 @@ Public Property Get FormattedResource() As String
136137

137138
' Only load parameters to querystring if GET request (otherwise they are added to the body)
138139
If Me.Method = httpGET Then
139-
FormattedResource = FormattedResource & RestHelpers.DictionariesToUrlEncodedString(Me.QuerystringParams, Me.Parameters)
140+
FormattedResource = FormattedResource & RestHelpers.DictionariesToUrlEncodedString(Me.Parameters, Me.QuerystringParams)
140141
Else
141142
FormattedResource = FormattedResource & RestHelpers.DictionariesToUrlEncodedString(Me.QuerystringParams)
142143
End If
@@ -147,24 +148,30 @@ End Property
147148
Public Property Get Body() As String
148149
' Add body if it's defined or parameters have been set and it is not a GET request
149150
If Not pBody Is Nothing Or pBodyString <> "" Or (Me.Parameters.count > 0 And Me.Method <> httpGET) Then
150-
Select Case Me.Format
151-
' (Currently only JSON is supported)
152-
Case Else
153-
If pBodyString <> "" Then
154-
If Me.Parameters.count > 0 And Me.Method <> httpGET Then
155-
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)
156163
Else
157-
Body = pBodyString
164+
Body = RestHelpers.DictionariesToUrlEncodedString(pBody)
158165
End If
159-
Else
166+
Case AvailableFormats.json
160167
If Me.Method <> httpGET Then
161168
' Combine defined body and parameters and convert to JSON
162-
Body = RestHelpers.ConvertToJSON(CombineObjects(pBody, Me.Parameters))
169+
Body = RestHelpers.ConvertToJSON(CombineObjects(Me.Parameters, pBody))
163170
Else
164171
Body = RestHelpers.ConvertToJSON(pBody)
165172
End If
166-
End If
167-
End Select
173+
End Select
174+
End If
168175
End If
169176
End Property
170177

@@ -200,7 +207,9 @@ End Property
200207

201208
Public Property Get FormatName() As String
202209
Select Case Me.Format
203-
Case Else
210+
Case AvailableFormats.formurlencoded
211+
FormatName = "form-urlencoded"
212+
Case AvailableFormats.json
204213
FormatName = "json"
205214
End Select
206215
End Property
@@ -210,12 +219,10 @@ Public Property Get ContentType() As String
210219
ContentType = pContentType
211220
Else
212221
Select Case Me.Format
213-
Case Else
214-
If Me.Method <> httpGET And Me.Parameters.count > 0 Then
215-
ContentType = "application/x-www-form-urlencoded;charset=UTF-8"
216-
Else
217-
ContentType = "application/json"
218-
End If
222+
Case AvailableFormats.formurlencoded
223+
ContentType = "application/x-www-form-urlencoded;charset=UTF-8"
224+
Case AvailableFormats.json
225+
ContentType = "application/json"
219226
End Select
220227
End If
221228
End Property

0 commit comments

Comments
 (0)