@@ -29,7 +29,7 @@ Private pParameters As Dictionary
29
29
Private pQuerystringParams As Dictionary
30
30
Private pUrlSegments As Dictionary
31
31
Private pCookies As Dictionary
32
- Private pBody As Dictionary
32
+ Private pBody As Variant
33
33
Private pBodyString As String
34
34
Private pContentType As String
35
35
Private pContentLength As Long
@@ -145,26 +145,42 @@ End Property
145
145
146
146
Public Property Get Body() As String
147
147
' Add body if it's defined or parameters have been set and it is not a GET request
148
- If Not pBody Is Nothing Or pBodyString <> "" Or (Me.Parameters.count > 0 And Me.Method <> httpGET) Then
148
+ If Not IsEmpty( pBody) Or pBodyString <> "" Or (Me.Parameters.count > 0 And Me.Method <> httpGET) Then
149
149
If pBodyString <> "" Then
150
150
If Me.Parameters.count > 0 And Me.Method <> httpGET Then
151
151
Err.Raise vbObjectError + 1 , "RestRequest.Body" , "Unable to combine body string and parameters"
152
152
Else
153
153
Body = pBodyString
154
154
End If
155
155
Else
156
+ If RestHelpers.IsArray(pBody) And Me.Parameters.count > 0 And Me.Method <> httpGET Then
157
+ Err.Raise vbObjectError + 1 , "RestRequest.Body" , "Unable to combine body array and parameters"
158
+ End If
159
+
156
160
Select Case Me.Format
157
161
Case AvailableFormats.formurlencoded
158
162
If Me.Method <> httpGET Then
159
- ' Combine defined body and parameters and convert to JSON
160
- Body = RestHelpers.DictionariesToUrlEncodedString(Me.Parameters, pBody)
163
+ If Me.Parameters.count > 0 And Not IsEmpty(pBody) Then
164
+ ' Combine defined body and parameters and convert to JSON
165
+ Body = RestHelpers.ConvertToUrlEncoded(CombineObjects(Me.Parameters, pBody))
166
+ ElseIf Me.Parameters.count > 0 Then
167
+ Body = RestHelpers.ConvertToUrlEncoded(Me.Parameters)
168
+ Else
169
+ Body = RestHelpers.ConvertToUrlEncoded(pBody)
170
+ End If
161
171
Else
162
- Body = RestHelpers.DictionariesToUrlEncodedString (pBody)
172
+ Body = RestHelpers.ConvertToUrlEncoded (pBody)
163
173
End If
164
174
Case AvailableFormats.json
165
175
If Me.Method <> httpGET Then
166
- ' Combine defined body and parameters and convert to JSON
167
- Body = RestHelpers.ConvertToJSON(CombineObjects(Me.Parameters, pBody))
176
+ If Me.Parameters.count > 0 And Not IsEmpty(pBody) Then
177
+ ' Combine defined body and parameters and convert to JSON
178
+ Body = RestHelpers.ConvertToJSON(CombineObjects(Me.Parameters, pBody))
179
+ ElseIf Me.Parameters.count > 0 Then
180
+ Body = RestHelpers.ConvertToJSON(Me.Parameters)
181
+ Else
182
+ Body = RestHelpers.ConvertToJSON(pBody)
183
+ End If
168
184
Else
169
185
Body = RestHelpers.ConvertToJSON(pBody)
170
186
End If
@@ -343,11 +359,17 @@ End Sub
343
359
''
344
360
' Add body to request
345
361
'
346
- ' @param {Dictionary } bodyVal Object to add to body (will be converted to string)
362
+ ' @param {Variant } bodyVal Object/Collection/Array to add to body (will be converted to string)
347
363
' --------------------------------------------- '
348
364
349
- Public Function AddBody (BodyVal As Dictionary )
350
- Set pBody = BodyVal
365
+ Public Function AddBody (BodyVal As Variant )
366
+ If VarType(BodyVal) = vbObject Then
367
+ Set pBody = BodyVal
368
+ ElseIf RestHelpers.IsArray(BodyVal) Then
369
+ pBody = BodyVal
370
+ Else
371
+ pBodyString = BodyVal
372
+ End If
351
373
End Function
352
374
353
375
''
0 commit comments