@@ -140,19 +140,6 @@ End Type
140
140
#End If
141
141
' === End VBA-UTC
142
142
143
- #If Mac Then
144
- #ElseIf VBA7 Then
145
-
146
- Private Declare PtrSafe Sub json_CopyMemory Lib "kernel32 " Alias "RtlMoveMemory " _
147
- (json_MemoryDestination As Any , json_MemorySource As Any , ByVal json_ByteLength As Long )
148
-
149
- #Else
150
-
151
- Private Declare Sub json_CopyMemory Lib "kernel32 " Alias "RtlMoveMemory " _
152
- (json_MemoryDestination As Any , json_MemorySource As Any , ByVal json_ByteLength As Long )
153
-
154
- #End If
155
-
156
143
Private Type json_Options
157
144
' VBA only stores 15 significant digits, so any numbers larger than that are truncated
158
145
' This can lead to issues when BIGINT's are used (e.g. for Ids or Credit Cards), as they will be invalid above 15 digits
@@ -210,7 +197,7 @@ End Function
210
197
' @return {String}
211
198
''
212
199
Public Function ConvertToJson (ByVal JsonValue As Variant , Optional ByVal Whitespace As Variant , Optional ByVal json_CurrentIndentation As Long = 0 ) As String
213
- Dim json_buffer As String
200
+ Dim json_Buffer As String
214
201
Dim json_BufferPosition As Long
215
202
Dim json_BufferLength As Long
216
203
Dim json_Index As Long
@@ -271,7 +258,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
271
258
End If
272
259
273
260
' Array
274
- json_BufferAppend json_buffer , "[" , json_BufferPosition, json_BufferLength
261
+ json_BufferAppend json_Buffer , "[" , json_BufferPosition, json_BufferLength
275
262
276
263
On Error Resume Next
277
264
@@ -286,21 +273,21 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
286
273
json_IsFirstItem = False
287
274
Else
288
275
' Append comma to previous line
289
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
276
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
290
277
End If
291
278
292
279
If json_LBound2D >= 0 And json_UBound2D >= 0 Then
293
280
' 2D Array
294
281
If json_PrettyPrint Then
295
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
282
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
296
283
End If
297
- json_BufferAppend json_buffer , json_Indentation & "[" , json_BufferPosition, json_BufferLength
284
+ json_BufferAppend json_Buffer , json_Indentation & "[" , json_BufferPosition, json_BufferLength
298
285
299
286
For json_Index2D = json_LBound2D To json_UBound2D
300
287
If json_IsFirstItem2D Then
301
288
json_IsFirstItem2D = False
302
289
Else
303
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
290
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
304
291
End If
305
292
306
293
json_Converted = ConvertToJson(JsonValue(json_Index, json_Index2D), Whitespace, json_CurrentIndentation + 2 )
@@ -317,14 +304,14 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
317
304
json_Converted = vbNewLine & json_InnerIndentation & json_Converted
318
305
End If
319
306
320
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
307
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
321
308
Next json_Index2D
322
309
323
310
If json_PrettyPrint Then
324
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
311
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
325
312
End If
326
313
327
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
314
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
328
315
json_IsFirstItem2D = True
329
316
Else
330
317
' 1D Array
@@ -342,15 +329,15 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
342
329
json_Converted = vbNewLine & json_Indentation & json_Converted
343
330
End If
344
331
345
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
332
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
346
333
End If
347
334
Next json_Index
348
335
End If
349
336
350
337
On Error GoTo 0
351
338
352
339
If json_PrettyPrint Then
353
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
340
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
354
341
355
342
If VBA.VarType(Whitespace) = VBA.vbString Then
356
343
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -359,9 +346,9 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
359
346
End If
360
347
End If
361
348
362
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
349
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
363
350
364
- ConvertToJson = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
351
+ ConvertToJson = json_BufferToString(json_Buffer , json_BufferPosition)
365
352
366
353
' Dictionary or Collection
367
354
Case VBA.vbObject
@@ -375,7 +362,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
375
362
376
363
' Dictionary
377
364
If VBA.TypeName(JsonValue) = "Dictionary" Then
378
- json_BufferAppend json_buffer , "{" , json_BufferPosition, json_BufferLength
365
+ json_BufferAppend json_Buffer , "{" , json_BufferPosition, json_BufferLength
379
366
For Each json_Key In JsonValue.Keys
380
367
' For Objects, undefined (Empty/Nothing) is not added to object
381
368
json_Converted = ConvertToJson(JsonValue(json_Key), Whitespace, json_CurrentIndentation + 1 )
@@ -389,7 +376,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
389
376
If json_IsFirstItem Then
390
377
json_IsFirstItem = False
391
378
Else
392
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
379
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
393
380
End If
394
381
395
382
If json_PrettyPrint Then
@@ -398,12 +385,12 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
398
385
json_Converted = """" & json_Key & """:" & json_Converted
399
386
End If
400
387
401
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
388
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
402
389
End If
403
390
Next json_Key
404
391
405
392
If json_PrettyPrint Then
406
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
393
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
407
394
408
395
If VBA.VarType(Whitespace) = VBA.vbString Then
409
396
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -412,16 +399,16 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
412
399
End If
413
400
End If
414
401
415
- json_BufferAppend json_buffer , json_Indentation & "}" , json_BufferPosition, json_BufferLength
402
+ json_BufferAppend json_Buffer , json_Indentation & "}" , json_BufferPosition, json_BufferLength
416
403
417
404
' Collection
418
405
ElseIf VBA.TypeName(JsonValue) = "Collection" Then
419
- json_BufferAppend json_buffer , "[" , json_BufferPosition, json_BufferLength
406
+ json_BufferAppend json_Buffer , "[" , json_BufferPosition, json_BufferLength
420
407
For Each json_Value In JsonValue
421
408
If json_IsFirstItem Then
422
409
json_IsFirstItem = False
423
410
Else
424
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
411
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
425
412
End If
426
413
427
414
json_Converted = ConvertToJson(json_Value, Whitespace, json_CurrentIndentation + 1 )
@@ -438,11 +425,11 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
438
425
json_Converted = vbNewLine & json_Indentation & json_Converted
439
426
End If
440
427
441
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
428
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
442
429
Next json_Value
443
430
444
431
If json_PrettyPrint Then
445
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
432
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
446
433
447
434
If VBA.VarType(Whitespace) = VBA.vbString Then
448
435
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -451,10 +438,10 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
451
438
End If
452
439
End If
453
440
454
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
441
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
455
442
End If
456
443
457
- ConvertToJson = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
444
+ ConvertToJson = json_BufferToString(json_Buffer , json_BufferPosition)
458
445
Case VBA.vbInteger, VBA.vbLong, VBA.vbSingle, VBA.vbDouble, VBA.vbCurrency, VBA.vbDecimal
459
446
' Number (use decimals for numbers)
460
447
ConvertToJson = VBA.Replace(JsonValue, "," , "." )
@@ -558,7 +545,7 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
558
545
Dim json_Quote As String
559
546
Dim json_Char As String
560
547
Dim json_Code As String
561
- Dim json_buffer As String
548
+ Dim json_Buffer As String
562
549
Dim json_BufferPosition As Long
563
550
Dim json_BufferLength As Long
564
551
@@ -579,36 +566,36 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
579
566
580
567
Select Case json_Char
581
568
Case """" , "\" , "/" , "'"
582
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
569
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
583
570
json_Index = json_Index + 1
584
571
Case "b"
585
- json_BufferAppend json_buffer , vbBack, json_BufferPosition, json_BufferLength
572
+ json_BufferAppend json_Buffer , vbBack, json_BufferPosition, json_BufferLength
586
573
json_Index = json_Index + 1
587
574
Case "f"
588
- json_BufferAppend json_buffer , vbFormFeed, json_BufferPosition, json_BufferLength
575
+ json_BufferAppend json_Buffer , vbFormFeed, json_BufferPosition, json_BufferLength
589
576
json_Index = json_Index + 1
590
577
Case "n"
591
- json_BufferAppend json_buffer , vbCrLf, json_BufferPosition, json_BufferLength
578
+ json_BufferAppend json_Buffer , vbCrLf, json_BufferPosition, json_BufferLength
592
579
json_Index = json_Index + 1
593
580
Case "r"
594
- json_BufferAppend json_buffer , vbCr, json_BufferPosition, json_BufferLength
581
+ json_BufferAppend json_Buffer , vbCr, json_BufferPosition, json_BufferLength
595
582
json_Index = json_Index + 1
596
583
Case "t"
597
- json_BufferAppend json_buffer , vbTab, json_BufferPosition, json_BufferLength
584
+ json_BufferAppend json_Buffer , vbTab, json_BufferPosition, json_BufferLength
598
585
json_Index = json_Index + 1
599
586
Case "u"
600
587
' Unicode character escape (e.g. \u00a9 = Copyright)
601
588
json_Index = json_Index + 1
602
589
json_Code = VBA.Mid$(json_String, json_Index, 4 )
603
- json_BufferAppend json_buffer , VBA.ChrW(VBA.Val("&h" + json_Code)), json_BufferPosition, json_BufferLength
590
+ json_BufferAppend json_Buffer , VBA.ChrW(VBA.Val("&h" + json_Code)), json_BufferPosition, json_BufferLength
604
591
json_Index = json_Index + 4
605
592
End Select
606
593
Case json_Quote
607
- json_ParseString = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
594
+ json_ParseString = json_BufferToString(json_Buffer , json_BufferPosition)
608
595
json_Index = json_Index + 1
609
596
Exit Function
610
597
Case Else
611
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
598
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
612
599
json_Index = json_Index + 1
613
600
End Select
614
601
Loop
@@ -694,7 +681,7 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
694
681
Dim json_Index As Long
695
682
Dim json_Char As String
696
683
Dim json_AscCode As Long
697
- Dim json_buffer As String
684
+ Dim json_Buffer As String
698
685
Dim json_BufferPosition As Long
699
686
Dim json_BufferLength As Long
700
687
@@ -743,10 +730,10 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
743
730
json_Char = "\u" & VBA.Right$("0000" & VBA.Hex$(json_AscCode), 4 )
744
731
End Select
745
732
746
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
733
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
747
734
Next json_Index
748
735
749
- json_Encode = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
736
+ json_Encode = json_BufferToString(json_Buffer , json_BufferPosition)
750
737
End Function
751
738
752
739
Private Function json_Peek (json_String As String , ByVal json_Index As Long , Optional json_NumberOfCharacters As Long = 1 ) As String
@@ -773,7 +760,6 @@ Private Function json_StringIsLargeNumber(json_String As Variant) As Boolean
773
760
' Length with be at least 16 characters and assume will be less than 100 characters
774
761
If json_Length >= 16 And json_Length <= 100 Then
775
762
Dim json_CharCode As String
776
- Dim json_Index As Long
777
763
778
764
json_StringIsLargeNumber = True
779
765
@@ -819,13 +805,10 @@ Private Function json_ParseErrorMessage(json_String As String, ByRef json_Index
819
805
ErrorMessage
820
806
End Function
821
807
822
- Private Sub json_BufferAppend (ByRef json_buffer As String , _
808
+ Private Sub json_BufferAppend (ByRef json_Buffer As String , _
823
809
ByRef json_Append As Variant , _
824
810
ByRef json_BufferPosition As Long , _
825
811
ByRef json_BufferLength As Long )
826
- #If Mac Then
827
- json_buffer = json_buffer & json_Append
828
- #Else
829
812
' VBA can be slow to append strings due to allocating a new string for each append
830
813
' Instead of using the traditional append, allocate a large empty string and then copy string at append position
831
814
'
@@ -839,71 +822,40 @@ Private Sub json_BufferAppend(ByRef json_buffer As String, _
839
822
' Buffer: "abc "
840
823
' Buffer Length: 10
841
824
'
842
- ' Copy memory for "def" into buffer at position 3 (0-based)
825
+ ' Put "def" into buffer at position 3 (0-based)
843
826
' Buffer: "abcdef "
844
827
'
845
828
' Approach based on cStringBuilder from vbAccelerator
846
829
' http://www.vbaccelerator.com/home/VB/Code/Techniques/RunTime_Debug_Tracing/VB6_Tracer_Utility_zip_cStringBuilder_cls.asp
830
+ '
831
+ ' and clsStringAppend from Philip Swannell
832
+ ' https://github.com/VBA-tools/VBA-JSON/pull/82
847
833
848
834
Dim json_AppendLength As Long
849
835
Dim json_LengthPlusPosition As Long
850
836
851
- json_AppendLength = VBA.LenB (json_Append)
837
+ json_AppendLength = VBA.Len (json_Append)
852
838
json_LengthPlusPosition = json_AppendLength + json_BufferPosition
853
839
854
840
If json_LengthPlusPosition > json_BufferLength Then
855
- ' Appending would overflow buffer, add chunks until buffer is long enough
856
- Dim json_TemporaryLength As Long
857
-
858
- json_TemporaryLength = json_BufferLength
859
- Do While json_TemporaryLength < json_LengthPlusPosition
860
- ' Initially, initialize string with 255 characters,
861
- ' then add large chunks (8192) after that
862
- '
863
- ' Size: # Characters x 2 bytes / character
864
- If json_TemporaryLength = 0 Then
865
- json_TemporaryLength = json_TemporaryLength + 510
866
- Else
867
- json_TemporaryLength = json_TemporaryLength + 16384
868
- End If
869
- Loop
841
+ ' Appending would overflow buffer, add chunk
842
+ ' (double buffer length or append length, whichever is bigger)
843
+ Dim json_AddedLength As Long
844
+ json_AddedLength = IIf (json_AppendLength > json_BufferLength, json_AppendLength, json_BufferLength)
870
845
871
- json_buffer = json_buffer & VBA.Space$((json_TemporaryLength - json_BufferLength) \ 2 )
872
- json_BufferLength = json_TemporaryLength
846
+ json_Buffer = json_Buffer & VBA.Space$(json_AddedLength )
847
+ json_BufferLength = json_BufferLength + json_AddedLength
873
848
End If
874
849
875
- ' Copy memory from append to buffer at buffer position
876
- json_CopyMemory ByVal json_UnsignedAdd(StrPtr(json_buffer), _
877
- json_BufferPosition), _
878
- ByVal StrPtr(json_Append), _
879
- json_AppendLength
880
-
850
+ ' Note: Namespacing with VBA.Mid$ doesn't work properly here, throwing compile error:
851
+ ' Function call on left-hand side of assignment must return Variant or Object
852
+ Mid$(json_Buffer, json_BufferPosition + 1 , json_AppendLength) = CStr(json_Append)
881
853
json_BufferPosition = json_BufferPosition + json_AppendLength
882
- #End If
883
854
End Sub
884
855
885
- Private Function json_BufferToString (ByRef json_buffer As String , ByVal json_BufferPosition As Long , ByVal json_BufferLength As Long ) As String
886
- #If Mac Then
887
- json_BufferToString = json_buffer
888
- #Else
856
+ Private Function json_BufferToString (ByRef json_Buffer As String , ByVal json_BufferPosition As Long ) As String
889
857
If json_BufferPosition > 0 Then
890
- json_BufferToString = VBA.Left$(json_buffer, json_BufferPosition \ 2 )
891
- End If
892
- #End If
893
- End Function
894
-
895
- #If VBA7 Then
896
- Private Function json_UnsignedAdd (json_Start As LongPtr , json_Increment As Long ) As LongPtr
897
- #Else
898
- Private Function json_UnsignedAdd (json_Start As Long , json_Increment As Long ) As Long
899
- #End If
900
-
901
- If json_Start And &H80000000 Then
902
- json_UnsignedAdd = json_Start + json_Increment
903
- ElseIf (json_Start Or &H80000000 ) < -json_Increment Then
904
- json_UnsignedAdd = json_Start + json_Increment
905
- Else
906
- json_UnsignedAdd = (json_Start + &H80000000 ) + (json_Increment + &H80000000 )
858
+ json_BufferToString = VBA.Left$(json_Buffer, json_BufferPosition)
907
859
End If
908
860
End Function
909
861
0 commit comments