Skip to content

Commit 0a7fb40

Browse files
committed
Merge pull request #39 from timhall/array-body
Allow Array and Collection for Body values
2 parents 639cde5 + 771140c commit 0a7fb40

File tree

5 files changed

+54
-14
lines changed

5 files changed

+54
-14
lines changed

Excel-REST - Blank.xlsm

15 KB
Binary file not shown.

specs/Excel-REST - Specs.xlsm

71.4 KB
Binary file not shown.

src/RestClient.cls

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -129,7 +129,7 @@ End Function
129129
' @return {RestResponse} Response
130130
' --------------------------------------------- '
131131

132-
Public Function PostJSON(Url As String, Body As Dictionary, Optional Options As Dictionary) As RestResponse
132+
Public Function PostJSON(Url As String, Body As Variant, Optional Options As Dictionary) As RestResponse
133133
Dim Request As RestRequest
134134
Set Request = RestHelpers.CreateRequestFromOptions(Options)
135135
Request.Resource = Url

src/RestHelpers.bas

Lines changed: 21 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -121,7 +121,7 @@ End Function
121121
' @return {String}
122122
' --------------------------------------------- '
123123

124-
Public Function ConvertToJSON(Obj As Object) As String
124+
Public Function ConvertToJSON(Obj As Variant) As String
125125
ConvertToJSON = json_toString(Obj)
126126
End Function
127127

@@ -296,14 +296,32 @@ Public Function FilterObject(ByVal Original As Dictionary, Whitelist As Variant)
296296
Set FilterObject = Filtered
297297
End Function
298298

299+
Public Function IsArray(Obj As Variant) As Boolean
300+
If Not IsEmpty(Obj) Then
301+
If VarType(Obj) = vbObject Then
302+
If TypeOf Obj Is Collection Then
303+
IsArray = True
304+
End If
305+
ElseIf VarType(Obj) = vbArray Or VarType(Obj) = 8204 Then
306+
' VarType = 8204 seems to arise from Array(...) constructor
307+
IsArray = True
308+
End If
309+
End If
310+
End Function
311+
299312
''
300313
' Convert dictionary to url encoded string
301314
'
302-
' @param {Dictionary} Obj
315+
' @param {Variant} Obj
303316
' @return {String} UrlEncoded string (e.g. a=123&b=456&...)
304317
' --------------------------------------------- '
305318

306-
Public Function ConvertToUrlEncoded(Obj As Dictionary) As String
319+
Public Function ConvertToUrlEncoded(Obj As Variant) As String
320+
If IsArray(Obj) Then
321+
' TODO Handle arrays and collections
322+
Err.Raise vbObjectError + 1, "RestHelpers.ConvertToUrlEncoded", "Arrays are not currently supported by ConvertToUrlEncoded"
323+
End If
324+
307325
ConvertToUrlEncoded = DictionariesToUrlEncodedString(Obj)
308326
End Function
309327
Public Function DictionariesToUrlEncodedString(ParamArray Dictionaries() As Variant) As String

src/RestRequest.cls

Lines changed: 32 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ Private pParameters As Dictionary
2929
Private pQuerystringParams As Dictionary
3030
Private pUrlSegments As Dictionary
3131
Private pCookies As Dictionary
32-
Private pBody As Dictionary
32+
Private pBody As Variant
3333
Private pBodyString As String
3434
Private pContentType As String
3535
Private pContentLength As Long
@@ -145,26 +145,42 @@ End Property
145145

146146
Public 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
351373
End Function
352374

353375
''

0 commit comments

Comments
 (0)