@@ -29,7 +29,7 @@ Private pParameters As Dictionary
2929Private pQuerystringParams As Dictionary
3030Private pUrlSegments As Dictionary
3131Private pCookies As Dictionary
32- Private pBody As Dictionary
32+ Private pBody As Variant
3333Private pBodyString As String
3434Private pContentType As String
3535Private pContentLength As Long
@@ -145,26 +145,42 @@ End Property
145145
146146Public Property Get Body() As String
147147 ' 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
149149 If pBodyString <> "" Then
150150 If Me.Parameters.count > 0 And Me.Method <> httpGET Then
151151 Err.Raise vbObjectError + 1 , "RestRequest.Body" , "Unable to combine body string and parameters"
152152 Else
153153 Body = pBodyString
154154 End If
155155 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+
156160 Select Case Me.Format
157161 Case AvailableFormats.formurlencoded
158162 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
161171 Else
162- Body = RestHelpers.DictionariesToUrlEncodedString (pBody)
172+ Body = RestHelpers.ConvertToUrlEncoded (pBody)
163173 End If
164174 Case AvailableFormats.json
165175 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
168184 Else
169185 Body = RestHelpers.ConvertToJSON(pBody)
170186 End If
@@ -343,11 +359,17 @@ End Sub
343359''
344360' Add body to request
345361'
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)
347363' --------------------------------------------- '
348364
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
351373End Function
352374
353375''
0 commit comments