@@ -195,6 +195,8 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant)
195195 Dim json_Key As Variant
196196 Dim json_Value As Variant
197197 Dim json_DateStr As String
198+ Dim json_Converted As String
199+ Dim json_SkipItem As Boolean
198200
199201 json_LBound = -1
200202 json_UBound = -1
@@ -204,7 +206,7 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant)
204206 json_IsFirstItem2D = True
205207
206208 Select Case VBA.VarType(json_DictionaryCollectionOrArray)
207- Case VBA.vbNull, VBA.vbEmpty
209+ Case VBA.vbNull
208210 ConvertToJson = "null"
209211 Case VBA.vbDate
210212 ' Date
@@ -253,17 +255,33 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant)
253255 json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
254256 End If
255257
256- json_BufferAppend json_buffer, _
257- ConvertToJson(json_DictionaryCollectionOrArray(json_Index, json_Index2D)), _
258- json_BufferPosition, json_BufferLength
258+ json_Converted = ConvertToJson(json_DictionaryCollectionOrArray(json_Index, json_Index2D))
259+
260+ ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
261+ If json_Converted = "" Then
262+ ' (nest to only check if converted = "")
263+ If json_IsUndefined(json_DictionaryCollectionOrArray(json_Index, json_Index2D)) Then
264+ json_Converted = "null"
265+ End If
266+ End If
267+
268+ json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
259269 Next json_Index2D
260270
261271 json_BufferAppend json_buffer, "]" , json_BufferPosition, json_BufferLength
262272 json_IsFirstItem2D = True
263273 Else
264- json_BufferAppend json_buffer, _
265- ConvertToJson(json_DictionaryCollectionOrArray(json_Index)), _
266- json_BufferPosition, json_BufferLength
274+ json_Converted = ConvertToJson(json_DictionaryCollectionOrArray(json_Index))
275+
276+ ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
277+ If json_Converted = "" Then
278+ ' (nest to only check if converted = "")
279+ If json_IsUndefined(json_DictionaryCollectionOrArray(json_Index)) Then
280+ json_Converted = "null"
281+ End If
282+ End If
283+
284+ json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
267285 End If
268286 Next json_Index
269287 End If
@@ -280,15 +298,23 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant)
280298 If VBA.TypeName(json_DictionaryCollectionOrArray) = "Dictionary" Then
281299 json_BufferAppend json_buffer, "{" , json_BufferPosition, json_BufferLength
282300 For Each json_Key In json_DictionaryCollectionOrArray.Keys
283- If json_IsFirstItem Then
284- json_IsFirstItem = False
301+ ' For Objects, undefined (Empty/Nothing) is not added to object
302+ json_Converted = ConvertToJson(json_DictionaryCollectionOrArray(json_Key))
303+ If json_Converted = "" Then
304+ json_SkipItem = json_IsUndefined(json_DictionaryCollectionOrArray(json_Key))
285305 Else
286- json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
306+ json_SkipItem = False
307+ End If
308+
309+ If Not json_SkipItem Then
310+ If json_IsFirstItem Then
311+ json_IsFirstItem = False
312+ Else
313+ json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
314+ End If
315+
316+ json_BufferAppend json_buffer, """" & json_Key & """:" & json_Converted, json_BufferPosition, json_BufferLength
287317 End If
288-
289- json_BufferAppend json_buffer, _
290- """" & json_Key & """:" & ConvertToJson(json_DictionaryCollectionOrArray(json_Key)), _
291- json_BufferPosition, json_BufferLength
292318 Next json_Key
293319 json_BufferAppend json_buffer, "}" , json_BufferPosition, json_BufferLength
294320
@@ -302,18 +328,30 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant)
302328 json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
303329 End If
304330
305- json_BufferAppend json_buffer, _
306- ConvertToJson(json_Value), _
307- json_BufferPosition, json_BufferLength
331+ json_Converted = ConvertToJson(json_Value)
332+
333+ ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
334+ If json_Converted = "" Then
335+ ' (nest to only check if converted = "")
336+ If json_IsUndefined(json_Value) Then
337+ json_Converted = "null"
338+ End If
339+ End If
340+
341+ json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
308342 Next json_Value
309343 json_BufferAppend json_buffer, "]" , json_BufferPosition, json_BufferLength
310344 End If
311345
312346 ConvertToJson = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
347+ Case VBA.vbInteger, VBA.vbLong, VBA.vbSingle, VBA.vbDouble, VBA.vbCurrency, VBA.vbDecimal
348+ ' Number (use decimals for numbers)
349+ ConvertToJson = VBA.Replace(json_DictionaryCollectionOrArray, "," , "." )
313350 Case Else
314- ' Number
351+ ' vbEmpty, vbError, vbDataObject, vbByte, vbUserDefinedType
352+ ' Use VBA's built-in to-string
315353 On Error Resume Next
316- ConvertToJson = VBA.Replace( json_DictionaryCollectionOrArray, "," , "." )
354+ ConvertToJson = json_DictionaryCollectionOrArray
317355 On Error GoTo 0
318356 End Select
319357End Function
@@ -526,6 +564,19 @@ Private Function json_ParseKey(json_String As String, ByRef json_Index As Long)
526564 End If
527565End Function
528566
567+ Private Function json_IsUndefined (ByVal json_Value As Variant ) As Boolean
568+ ' Empty / Nothing -> undefined
569+ Select Case VBA.VarType(json_Value)
570+ Case VBA.vbEmpty
571+ json_IsUndefined = True
572+ Case VBA.vbObject
573+ Select Case VBA.TypeName(json_DictionaryCollectionOrArray)
574+ Case "Empty" , "Nothing"
575+ json_IsUndefined = True
576+ End Select
577+ End Select
578+ End Function
579+
529580Private Function json_Encode (ByVal json_Text As Variant ) As String
530581 ' Reference: http://www.ietf.org/rfc/rfc4627.txt
531582 ' Escape: ", \, /, backspace, form feed, line feed, carriage return, tab
0 commit comments