@@ -154,34 +154,34 @@ Public JsonOptions As json_Options
154154' @return {Object} (Dictionary or Collection)
155155' @throws 10001 - JSON parse error
156156''
157- Public Function ParseJson (ByVal json_String As String ) As Object
157+ Public Function ParseJson (ByVal JsonString As String ) As Object
158158 Dim json_Index As Long
159159 json_Index = 1
160160
161161 ' Remove vbCr, vbLf, and vbTab from json_String
162- json_String = VBA.Replace(VBA.Replace(VBA.Replace(json_String , VBA.vbCr, "" ), VBA.vbLf, "" ), VBA.vbTab, "" )
162+ JsonString = VBA.Replace(VBA.Replace(VBA.Replace(JsonString , VBA.vbCr, "" ), VBA.vbLf, "" ), VBA.vbTab, "" )
163163
164- json_SkipSpaces json_String , json_Index
165- Select Case VBA.Mid$(json_String , json_Index, 1 )
164+ json_SkipSpaces JsonString , json_Index
165+ Select Case VBA.Mid$(JsonString , json_Index, 1 )
166166 Case "{"
167- Set ParseJson = json_ParseObject(json_String , json_Index)
167+ Set ParseJson = json_ParseObject(JsonString , json_Index)
168168 Case "["
169- Set ParseJson = json_ParseArray(json_String , json_Index)
169+ Set ParseJson = json_ParseArray(JsonString , json_Index)
170170 Case Else
171171 ' Error: Invalid JSON string
172- Err.Raise 10001 , "JSONConverter" , json_ParseErrorMessage(json_String , json_Index, "Expecting '{' or '['" )
172+ Err.Raise 10001 , "JSONConverter" , json_ParseErrorMessage(JsonString , json_Index, "Expecting '{' or '['" )
173173 End Select
174174End Function
175175
176176''
177177' Convert object (Dictionary/Collection/Array) to JSON
178178'
179179' @method ConvertToJson
180- ' @param {Variant} json_DictionaryCollectionOrArray (Dictionary, Collection, or Array)
181- ' @param {Integer|String} json_Whitespace "Pretty" print json with given number of spaces per indentation (Integer) or given string
180+ ' @param {Variant} JsonValue (Dictionary, Collection, or Array)
181+ ' @param {Integer|String} Whitespace "Pretty" print json with given number of spaces per indentation (Integer) or given string
182182' @return {String}
183183''
184- Public Function ConvertToJson (ByVal json_DictionaryCollectionOrArray As Variant , Optional ByVal json_Whitespace As Variant , Optional ByVal json_CurrentIndentation As Long = 0 ) As String
184+ Public Function ConvertToJson (ByVal JsonValue As Variant , Optional ByVal Whitespace As Variant , Optional ByVal json_CurrentIndentation As Long = 0 ) As String
185185 Dim json_buffer As String
186186 Dim json_BufferPosition As Long
187187 Dim json_BufferLength As Long
@@ -208,37 +208,37 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
208208 json_LBound2D = -1
209209 json_UBound2D = -1
210210 json_IsFirstItem2D = True
211- json_PrettyPrint = Not IsMissing(json_Whitespace )
211+ json_PrettyPrint = Not IsMissing(Whitespace )
212212
213- Select Case VBA.VarType(json_DictionaryCollectionOrArray )
213+ Select Case VBA.VarType(JsonValue )
214214 Case VBA.vbNull
215215 ConvertToJson = "null"
216216 Case VBA.vbDate
217217 ' Date
218- json_DateStr = ConvertToIso(VBA.CDate(json_DictionaryCollectionOrArray ))
218+ json_DateStr = ConvertToIso(VBA.CDate(JsonValue ))
219219
220220 ConvertToJson = """" & json_DateStr & """"
221221 Case VBA.vbString
222222 ' String (or large number encoded as string)
223- If Not JsonOptions.UseDoubleForLargeNumbers And json_StringIsLargeNumber(json_DictionaryCollectionOrArray ) Then
224- ConvertToJson = json_DictionaryCollectionOrArray
223+ If Not JsonOptions.UseDoubleForLargeNumbers And json_StringIsLargeNumber(JsonValue ) Then
224+ ConvertToJson = JsonValue
225225 Else
226- ConvertToJson = """" & json_Encode(json_DictionaryCollectionOrArray ) & """"
226+ ConvertToJson = """" & json_Encode(JsonValue ) & """"
227227 End If
228228 Case VBA.vbBoolean
229- If json_DictionaryCollectionOrArray Then
229+ If JsonValue Then
230230 ConvertToJson = "true"
231231 Else
232232 ConvertToJson = "false"
233233 End If
234234 Case VBA.vbArray To VBA.vbArray + VBA.vbByte
235235 If json_PrettyPrint Then
236- If VBA.VarType(json_Whitespace ) = VBA.vbString Then
237- json_Indentation = VBA.String $(json_CurrentIndentation + 1 , json_Whitespace )
238- json_InnerIndentation = VBA.String $(json_CurrentIndentation + 2 , json_Whitespace )
236+ If VBA.VarType(Whitespace ) = VBA.vbString Then
237+ json_Indentation = VBA.String $(json_CurrentIndentation + 1 , Whitespace )
238+ json_InnerIndentation = VBA.String $(json_CurrentIndentation + 2 , Whitespace )
239239 Else
240- json_Indentation = VBA.Space$((json_CurrentIndentation + 1 ) * json_Whitespace )
241- json_InnerIndentation = VBA.Space$((json_CurrentIndentation + 2 ) * json_Whitespace )
240+ json_Indentation = VBA.Space$((json_CurrentIndentation + 1 ) * Whitespace )
241+ json_InnerIndentation = VBA.Space$((json_CurrentIndentation + 2 ) * Whitespace )
242242 End If
243243 End If
244244
@@ -247,10 +247,10 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
247247
248248 On Error Resume Next
249249
250- json_LBound = LBound(json_DictionaryCollectionOrArray , 1 )
251- json_UBound = UBound(json_DictionaryCollectionOrArray , 1 )
252- json_LBound2D = LBound(json_DictionaryCollectionOrArray , 2 )
253- json_UBound2D = UBound(json_DictionaryCollectionOrArray , 2 )
250+ json_LBound = LBound(JsonValue , 1 )
251+ json_UBound = UBound(JsonValue , 1 )
252+ json_LBound2D = LBound(JsonValue , 2 )
253+ json_UBound2D = UBound(JsonValue , 2 )
254254
255255 If json_LBound >= 0 And json_UBound >= 0 Then
256256 For json_Index = json_LBound To json_UBound
@@ -275,12 +275,12 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
275275 json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
276276 End If
277277
278- json_Converted = ConvertToJson(json_DictionaryCollectionOrArray (json_Index, json_Index2D), json_Whitespace , json_CurrentIndentation + 2 )
278+ json_Converted = ConvertToJson(JsonValue (json_Index, json_Index2D), Whitespace , json_CurrentIndentation + 2 )
279279
280280 ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
281281 If json_Converted = "" Then
282282 ' (nest to only check if converted = "")
283- If json_IsUndefined(json_DictionaryCollectionOrArray (json_Index, json_Index2D)) Then
283+ If json_IsUndefined(JsonValue (json_Index, json_Index2D)) Then
284284 json_Converted = "null"
285285 End If
286286 End If
@@ -300,12 +300,12 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
300300 json_IsFirstItem2D = True
301301 Else
302302 ' 1D Array
303- json_Converted = ConvertToJson(json_DictionaryCollectionOrArray (json_Index), json_Whitespace , json_CurrentIndentation + 1 )
303+ json_Converted = ConvertToJson(JsonValue (json_Index), Whitespace , json_CurrentIndentation + 1 )
304304
305305 ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
306306 If json_Converted = "" Then
307307 ' (nest to only check if converted = "")
308- If json_IsUndefined(json_DictionaryCollectionOrArray (json_Index)) Then
308+ If json_IsUndefined(JsonValue (json_Index)) Then
309309 json_Converted = "null"
310310 End If
311311 End If
@@ -324,10 +324,10 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
324324 If json_PrettyPrint Then
325325 json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
326326
327- If VBA.VarType(json_Whitespace ) = VBA.vbString Then
328- json_Indentation = VBA.String $(json_CurrentIndentation, json_Whitespace )
327+ If VBA.VarType(Whitespace ) = VBA.vbString Then
328+ json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace )
329329 Else
330- json_Indentation = VBA.Space$(json_CurrentIndentation * json_Whitespace )
330+ json_Indentation = VBA.Space$(json_CurrentIndentation * Whitespace )
331331 End If
332332 End If
333333
@@ -338,21 +338,21 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
338338 ' Dictionary or Collection
339339 Case VBA.vbObject
340340 If json_PrettyPrint Then
341- If VBA.VarType(json_Whitespace ) = VBA.vbString Then
342- json_Indentation = VBA.String $(json_CurrentIndentation + 1 , json_Whitespace )
341+ If VBA.VarType(Whitespace ) = VBA.vbString Then
342+ json_Indentation = VBA.String $(json_CurrentIndentation + 1 , Whitespace )
343343 Else
344- json_Indentation = VBA.Space$((json_CurrentIndentation + 1 ) * json_Whitespace )
344+ json_Indentation = VBA.Space$((json_CurrentIndentation + 1 ) * Whitespace )
345345 End If
346346 End If
347347
348348 ' Dictionary
349- If VBA.TypeName(json_DictionaryCollectionOrArray ) = "Dictionary" Then
349+ If VBA.TypeName(JsonValue ) = "Dictionary" Then
350350 json_BufferAppend json_buffer, "{" , json_BufferPosition, json_BufferLength
351- For Each json_Key In json_DictionaryCollectionOrArray .Keys
351+ For Each json_Key In JsonValue .Keys
352352 ' For Objects, undefined (Empty/Nothing) is not added to object
353- json_Converted = ConvertToJson(json_DictionaryCollectionOrArray (json_Key), json_Whitespace , json_CurrentIndentation + 1 )
353+ json_Converted = ConvertToJson(JsonValue (json_Key), Whitespace , json_CurrentIndentation + 1 )
354354 If json_Converted = "" Then
355- json_SkipItem = json_IsUndefined(json_DictionaryCollectionOrArray (json_Key))
355+ json_SkipItem = json_IsUndefined(JsonValue (json_Key))
356356 Else
357357 json_SkipItem = False
358358 End If
@@ -377,26 +377,26 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
377377 If json_PrettyPrint Then
378378 json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
379379
380- If VBA.VarType(json_Whitespace ) = VBA.vbString Then
381- json_Indentation = VBA.String $(json_CurrentIndentation, json_Whitespace )
380+ If VBA.VarType(Whitespace ) = VBA.vbString Then
381+ json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace )
382382 Else
383- json_Indentation = VBA.Space$(json_CurrentIndentation * json_Whitespace )
383+ json_Indentation = VBA.Space$(json_CurrentIndentation * Whitespace )
384384 End If
385385 End If
386386
387387 json_BufferAppend json_buffer, json_Indentation & "}" , json_BufferPosition, json_BufferLength
388388
389389 ' Collection
390- ElseIf VBA.TypeName(json_DictionaryCollectionOrArray ) = "Collection" Then
390+ ElseIf VBA.TypeName(JsonValue ) = "Collection" Then
391391 json_BufferAppend json_buffer, "[" , json_BufferPosition, json_BufferLength
392- For Each json_Value In json_DictionaryCollectionOrArray
392+ For Each json_Value In JsonValue
393393 If json_IsFirstItem Then
394394 json_IsFirstItem = False
395395 Else
396396 json_BufferAppend json_buffer, "," , json_BufferPosition, json_BufferLength
397397 End If
398398
399- json_Converted = ConvertToJson(json_Value, json_Whitespace , json_CurrentIndentation + 1 )
399+ json_Converted = ConvertToJson(json_Value, Whitespace , json_CurrentIndentation + 1 )
400400
401401 ' For Arrays/Collections, undefined (Empty/Nothing) is treated as null
402402 If json_Converted = "" Then
@@ -416,10 +416,10 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
416416 If json_PrettyPrint Then
417417 json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
418418
419- If VBA.VarType(json_Whitespace ) = VBA.vbString Then
420- json_Indentation = VBA.String $(json_CurrentIndentation, json_Whitespace )
419+ If VBA.VarType(Whitespace ) = VBA.vbString Then
420+ json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace )
421421 Else
422- json_Indentation = VBA.Space$(json_CurrentIndentation * json_Whitespace )
422+ json_Indentation = VBA.Space$(json_CurrentIndentation * Whitespace )
423423 End If
424424 End If
425425
@@ -429,12 +429,12 @@ Public Function ConvertToJson(ByVal json_DictionaryCollectionOrArray As Variant,
429429 ConvertToJson = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
430430 Case VBA.vbInteger, VBA.vbLong, VBA.vbSingle, VBA.vbDouble, VBA.vbCurrency, VBA.vbDecimal
431431 ' Number (use decimals for numbers)
432- ConvertToJson = VBA.Replace(json_DictionaryCollectionOrArray , "," , "." )
432+ ConvertToJson = VBA.Replace(JsonValue , "," , "." )
433433 Case Else
434434 ' vbEmpty, vbError, vbDataObject, vbByte, vbUserDefinedType
435435 ' Use VBA's built-in to-string
436436 On Error Resume Next
437- ConvertToJson = json_DictionaryCollectionOrArray
437+ ConvertToJson = JsonValue
438438 On Error GoTo 0
439439 End Select
440440End Function
@@ -653,7 +653,7 @@ Private Function json_IsUndefined(ByVal json_Value As Variant) As Boolean
653653 Case VBA.vbEmpty
654654 json_IsUndefined = True
655655 Case VBA.vbObject
656- Select Case VBA.TypeName(json_DictionaryCollectionOrArray )
656+ Select Case VBA.TypeName(JsonValue )
657657 Case "Empty" , "Nothing"
658658 json_IsUndefined = True
659659 End Select
0 commit comments