Skip to content

Commit 284dc72

Browse files
authored
Merge pull request #101 from VBA-tools/append
Inline clsStringAppend
2 parents 0af3e4d + 45aff20 commit 284dc72

File tree

2 files changed

+55
-103
lines changed

2 files changed

+55
-103
lines changed

JsonConverter.bas

+54-102
Original file line numberDiff line numberDiff line change
@@ -140,19 +140,6 @@ End Type
140140
#End If
141141
' === End VBA-UTC
142142

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-
156143
Private Type json_Options
157144
' VBA only stores 15 significant digits, so any numbers larger than that are truncated
158145
' 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
210197
' @return {String}
211198
''
212199
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
214201
Dim json_BufferPosition As Long
215202
Dim json_BufferLength As Long
216203
Dim json_Index As Long
@@ -271,7 +258,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
271258
End If
272259

273260
' Array
274-
json_BufferAppend json_buffer, "[", json_BufferPosition, json_BufferLength
261+
json_BufferAppend json_Buffer, "[", json_BufferPosition, json_BufferLength
275262

276263
On Error Resume Next
277264

@@ -286,21 +273,21 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
286273
json_IsFirstItem = False
287274
Else
288275
' Append comma to previous line
289-
json_BufferAppend json_buffer, ",", json_BufferPosition, json_BufferLength
276+
json_BufferAppend json_Buffer, ",", json_BufferPosition, json_BufferLength
290277
End If
291278

292279
If json_LBound2D >= 0 And json_UBound2D >= 0 Then
293280
' 2D Array
294281
If json_PrettyPrint Then
295-
json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
282+
json_BufferAppend json_Buffer, vbNewLine, json_BufferPosition, json_BufferLength
296283
End If
297-
json_BufferAppend json_buffer, json_Indentation & "[", json_BufferPosition, json_BufferLength
284+
json_BufferAppend json_Buffer, json_Indentation & "[", json_BufferPosition, json_BufferLength
298285

299286
For json_Index2D = json_LBound2D To json_UBound2D
300287
If json_IsFirstItem2D Then
301288
json_IsFirstItem2D = False
302289
Else
303-
json_BufferAppend json_buffer, ",", json_BufferPosition, json_BufferLength
290+
json_BufferAppend json_Buffer, ",", json_BufferPosition, json_BufferLength
304291
End If
305292

306293
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
317304
json_Converted = vbNewLine & json_InnerIndentation & json_Converted
318305
End If
319306

320-
json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
307+
json_BufferAppend json_Buffer, json_Converted, json_BufferPosition, json_BufferLength
321308
Next json_Index2D
322309

323310
If json_PrettyPrint Then
324-
json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
311+
json_BufferAppend json_Buffer, vbNewLine, json_BufferPosition, json_BufferLength
325312
End If
326313

327-
json_BufferAppend json_buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
314+
json_BufferAppend json_Buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
328315
json_IsFirstItem2D = True
329316
Else
330317
' 1D Array
@@ -342,15 +329,15 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
342329
json_Converted = vbNewLine & json_Indentation & json_Converted
343330
End If
344331

345-
json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
332+
json_BufferAppend json_Buffer, json_Converted, json_BufferPosition, json_BufferLength
346333
End If
347334
Next json_Index
348335
End If
349336

350337
On Error GoTo 0
351338

352339
If json_PrettyPrint Then
353-
json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
340+
json_BufferAppend json_Buffer, vbNewLine, json_BufferPosition, json_BufferLength
354341

355342
If VBA.VarType(Whitespace) = VBA.vbString Then
356343
json_Indentation = VBA.String$(json_CurrentIndentation, Whitespace)
@@ -359,9 +346,9 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
359346
End If
360347
End If
361348

362-
json_BufferAppend json_buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
349+
json_BufferAppend json_Buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
363350

364-
ConvertToJson = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
351+
ConvertToJson = json_BufferToString(json_Buffer, json_BufferPosition)
365352

366353
' Dictionary or Collection
367354
Case VBA.vbObject
@@ -375,7 +362,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
375362

376363
' Dictionary
377364
If VBA.TypeName(JsonValue) = "Dictionary" Then
378-
json_BufferAppend json_buffer, "{", json_BufferPosition, json_BufferLength
365+
json_BufferAppend json_Buffer, "{", json_BufferPosition, json_BufferLength
379366
For Each json_Key In JsonValue.Keys
380367
' For Objects, undefined (Empty/Nothing) is not added to object
381368
json_Converted = ConvertToJson(JsonValue(json_Key), Whitespace, json_CurrentIndentation + 1)
@@ -389,7 +376,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
389376
If json_IsFirstItem Then
390377
json_IsFirstItem = False
391378
Else
392-
json_BufferAppend json_buffer, ",", json_BufferPosition, json_BufferLength
379+
json_BufferAppend json_Buffer, ",", json_BufferPosition, json_BufferLength
393380
End If
394381

395382
If json_PrettyPrint Then
@@ -398,12 +385,12 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
398385
json_Converted = """" & json_Key & """:" & json_Converted
399386
End If
400387

401-
json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
388+
json_BufferAppend json_Buffer, json_Converted, json_BufferPosition, json_BufferLength
402389
End If
403390
Next json_Key
404391

405392
If json_PrettyPrint Then
406-
json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
393+
json_BufferAppend json_Buffer, vbNewLine, json_BufferPosition, json_BufferLength
407394

408395
If VBA.VarType(Whitespace) = VBA.vbString Then
409396
json_Indentation = VBA.String$(json_CurrentIndentation, Whitespace)
@@ -412,16 +399,16 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
412399
End If
413400
End If
414401

415-
json_BufferAppend json_buffer, json_Indentation & "}", json_BufferPosition, json_BufferLength
402+
json_BufferAppend json_Buffer, json_Indentation & "}", json_BufferPosition, json_BufferLength
416403

417404
' Collection
418405
ElseIf VBA.TypeName(JsonValue) = "Collection" Then
419-
json_BufferAppend json_buffer, "[", json_BufferPosition, json_BufferLength
406+
json_BufferAppend json_Buffer, "[", json_BufferPosition, json_BufferLength
420407
For Each json_Value In JsonValue
421408
If json_IsFirstItem Then
422409
json_IsFirstItem = False
423410
Else
424-
json_BufferAppend json_buffer, ",", json_BufferPosition, json_BufferLength
411+
json_BufferAppend json_Buffer, ",", json_BufferPosition, json_BufferLength
425412
End If
426413

427414
json_Converted = ConvertToJson(json_Value, Whitespace, json_CurrentIndentation + 1)
@@ -438,11 +425,11 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
438425
json_Converted = vbNewLine & json_Indentation & json_Converted
439426
End If
440427

441-
json_BufferAppend json_buffer, json_Converted, json_BufferPosition, json_BufferLength
428+
json_BufferAppend json_Buffer, json_Converted, json_BufferPosition, json_BufferLength
442429
Next json_Value
443430

444431
If json_PrettyPrint Then
445-
json_BufferAppend json_buffer, vbNewLine, json_BufferPosition, json_BufferLength
432+
json_BufferAppend json_Buffer, vbNewLine, json_BufferPosition, json_BufferLength
446433

447434
If VBA.VarType(Whitespace) = VBA.vbString Then
448435
json_Indentation = VBA.String$(json_CurrentIndentation, Whitespace)
@@ -451,10 +438,10 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
451438
End If
452439
End If
453440

454-
json_BufferAppend json_buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
441+
json_BufferAppend json_Buffer, json_Indentation & "]", json_BufferPosition, json_BufferLength
455442
End If
456443

457-
ConvertToJson = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
444+
ConvertToJson = json_BufferToString(json_Buffer, json_BufferPosition)
458445
Case VBA.vbInteger, VBA.vbLong, VBA.vbSingle, VBA.vbDouble, VBA.vbCurrency, VBA.vbDecimal
459446
' Number (use decimals for numbers)
460447
ConvertToJson = VBA.Replace(JsonValue, ",", ".")
@@ -558,7 +545,7 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
558545
Dim json_Quote As String
559546
Dim json_Char As String
560547
Dim json_Code As String
561-
Dim json_buffer As String
548+
Dim json_Buffer As String
562549
Dim json_BufferPosition As Long
563550
Dim json_BufferLength As Long
564551

@@ -579,36 +566,36 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
579566

580567
Select Case json_Char
581568
Case """", "\", "/", "'"
582-
json_BufferAppend json_buffer, json_Char, json_BufferPosition, json_BufferLength
569+
json_BufferAppend json_Buffer, json_Char, json_BufferPosition, json_BufferLength
583570
json_Index = json_Index + 1
584571
Case "b"
585-
json_BufferAppend json_buffer, vbBack, json_BufferPosition, json_BufferLength
572+
json_BufferAppend json_Buffer, vbBack, json_BufferPosition, json_BufferLength
586573
json_Index = json_Index + 1
587574
Case "f"
588-
json_BufferAppend json_buffer, vbFormFeed, json_BufferPosition, json_BufferLength
575+
json_BufferAppend json_Buffer, vbFormFeed, json_BufferPosition, json_BufferLength
589576
json_Index = json_Index + 1
590577
Case "n"
591-
json_BufferAppend json_buffer, vbCrLf, json_BufferPosition, json_BufferLength
578+
json_BufferAppend json_Buffer, vbCrLf, json_BufferPosition, json_BufferLength
592579
json_Index = json_Index + 1
593580
Case "r"
594-
json_BufferAppend json_buffer, vbCr, json_BufferPosition, json_BufferLength
581+
json_BufferAppend json_Buffer, vbCr, json_BufferPosition, json_BufferLength
595582
json_Index = json_Index + 1
596583
Case "t"
597-
json_BufferAppend json_buffer, vbTab, json_BufferPosition, json_BufferLength
584+
json_BufferAppend json_Buffer, vbTab, json_BufferPosition, json_BufferLength
598585
json_Index = json_Index + 1
599586
Case "u"
600587
' Unicode character escape (e.g. \u00a9 = Copyright)
601588
json_Index = json_Index + 1
602589
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
604591
json_Index = json_Index + 4
605592
End Select
606593
Case json_Quote
607-
json_ParseString = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
594+
json_ParseString = json_BufferToString(json_Buffer, json_BufferPosition)
608595
json_Index = json_Index + 1
609596
Exit Function
610597
Case Else
611-
json_BufferAppend json_buffer, json_Char, json_BufferPosition, json_BufferLength
598+
json_BufferAppend json_Buffer, json_Char, json_BufferPosition, json_BufferLength
612599
json_Index = json_Index + 1
613600
End Select
614601
Loop
@@ -694,7 +681,7 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
694681
Dim json_Index As Long
695682
Dim json_Char As String
696683
Dim json_AscCode As Long
697-
Dim json_buffer As String
684+
Dim json_Buffer As String
698685
Dim json_BufferPosition As Long
699686
Dim json_BufferLength As Long
700687

@@ -743,10 +730,10 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
743730
json_Char = "\u" & VBA.Right$("0000" & VBA.Hex$(json_AscCode), 4)
744731
End Select
745732

746-
json_BufferAppend json_buffer, json_Char, json_BufferPosition, json_BufferLength
733+
json_BufferAppend json_Buffer, json_Char, json_BufferPosition, json_BufferLength
747734
Next json_Index
748735

749-
json_Encode = json_BufferToString(json_buffer, json_BufferPosition, json_BufferLength)
736+
json_Encode = json_BufferToString(json_Buffer, json_BufferPosition)
750737
End Function
751738

752739
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
773760
' Length with be at least 16 characters and assume will be less than 100 characters
774761
If json_Length >= 16 And json_Length <= 100 Then
775762
Dim json_CharCode As String
776-
Dim json_Index As Long
777763

778764
json_StringIsLargeNumber = True
779765

@@ -819,13 +805,10 @@ Private Function json_ParseErrorMessage(json_String As String, ByRef json_Index
819805
ErrorMessage
820806
End Function
821807

822-
Private Sub json_BufferAppend(ByRef json_buffer As String, _
808+
Private Sub json_BufferAppend(ByRef json_Buffer As String, _
823809
ByRef json_Append As Variant, _
824810
ByRef json_BufferPosition As Long, _
825811
ByRef json_BufferLength As Long)
826-
#If Mac Then
827-
json_buffer = json_buffer & json_Append
828-
#Else
829812
' VBA can be slow to append strings due to allocating a new string for each append
830813
' Instead of using the traditional append, allocate a large empty string and then copy string at append position
831814
'
@@ -839,71 +822,40 @@ Private Sub json_BufferAppend(ByRef json_buffer As String, _
839822
' Buffer: "abc "
840823
' Buffer Length: 10
841824
'
842-
' Copy memory for "def" into buffer at position 3 (0-based)
825+
' Put "def" into buffer at position 3 (0-based)
843826
' Buffer: "abcdef "
844827
'
845828
' Approach based on cStringBuilder from vbAccelerator
846829
' 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
847833

848834
Dim json_AppendLength As Long
849835
Dim json_LengthPlusPosition As Long
850836

851-
json_AppendLength = VBA.LenB(json_Append)
837+
json_AppendLength = VBA.Len(json_Append)
852838
json_LengthPlusPosition = json_AppendLength + json_BufferPosition
853839

854840
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)
870845

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
873848
End If
874849

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)
881853
json_BufferPosition = json_BufferPosition + json_AppendLength
882-
#End If
883854
End Sub
884855

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
889857
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)
907859
End If
908860
End Function
909861

specs/Specs.bas

+1-1
Original file line numberDiff line numberDiff line change
@@ -258,7 +258,7 @@ Public Function Specs() As SpecSuite
258258

259259
With Specs.It("should json-encode strings")
260260
Dim Strings As Variant
261-
Strings = Array("""\" & vbCrLf & vbTab & vbBack & vbFormFeed, ChrW(128) & ChrW(32767), "#$%&{|}~")
261+
Strings = Array("""\" & vbCr & vbLf & vbTab & vbBack & vbFormFeed, ChrW(128) & ChrW(32767), "#$%&{|}~")
262262

263263
JsonString = JsonConverter.ConvertToJson(Strings)
264264
.Expect(JsonString).ToEqual "[""\""\\\r\n\t\b\f"",""\u0080\u7FFF"",""#$%&{|}~""]"

0 commit comments

Comments
 (0)