@@ -236,19 +236,6 @@ End Type
236
236
#End If
237
237
' === End VBA-UTC
238
238
239
- #If Mac Then
240
- #ElseIf VBA7 Then
241
-
242
- Private Declare PtrSafe Sub json_CopyMemory Lib "kernel32 " Alias "RtlMoveMemory " _
243
- (json_MemoryDestination As Any , json_MemorySource As Any , ByVal json_ByteLength As Long )
244
-
245
- #Else
246
-
247
- Private Declare Sub json_CopyMemory Lib "kernel32 " Alias "RtlMoveMemory " _
248
- (json_MemoryDestination As Any , json_MemorySource As Any , ByVal json_ByteLength As Long )
249
-
250
- #End If
251
-
252
239
Private Type json_Options
253
240
' VBA only stores 15 significant digits, so any numbers larger than that are truncated
254
241
' 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
@@ -1990,7 +1977,7 @@ Private Function web_GetUrlEncodedKeyValue(Key As Variant, Value As Variant, Opt
1990
1977
End Function
1991
1978
1992
1979
''
1993
- ' VBA-JSON v2.2.4
1980
+ ' VBA-JSON v2.3.0
1994
1981
' (c) Tim Hall - https://github.com/VBA-tools/VBA-JSON
1995
1982
'
1996
1983
' JSON Converter for VBA
@@ -2076,7 +2063,7 @@ End Function
2076
2063
' @return {String}
2077
2064
''
2078
2065
Public Function ConvertToJson (ByVal JsonValue As Variant , Optional ByVal Whitespace As Variant , Optional ByVal json_CurrentIndentation As Long = 0 ) As String
2079
- Dim json_buffer As String
2066
+ Dim json_Buffer As String
2080
2067
Dim json_BufferPosition As Long
2081
2068
Dim json_BufferLength As Long
2082
2069
Dim json_Index As Long
@@ -2137,7 +2124,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2137
2124
End If
2138
2125
2139
2126
' Array
2140
- json_BufferAppend json_buffer , "[" , json_BufferPosition, json_BufferLength
2127
+ json_BufferAppend json_Buffer , "[" , json_BufferPosition, json_BufferLength
2141
2128
2142
2129
On Error Resume Next
2143
2130
@@ -2152,21 +2139,21 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2152
2139
json_IsFirstItem = False
2153
2140
Else
2154
2141
' Append comma to previous line
2155
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
2142
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
2156
2143
End If
2157
2144
2158
2145
If json_LBound2D >= 0 And json_UBound2D >= 0 Then
2159
2146
' 2D Array
2160
2147
If json_PrettyPrint Then
2161
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
2148
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
2162
2149
End If
2163
- json_BufferAppend json_buffer , json_Indentation & "[" , json_BufferPosition, json_BufferLength
2150
+ json_BufferAppend json_Buffer , json_Indentation & "[" , json_BufferPosition, json_BufferLength
2164
2151
2165
2152
For json_Index2D = json_LBound2D To json_UBound2D
2166
2153
If json_IsFirstItem2D Then
2167
2154
json_IsFirstItem2D = False
2168
2155
Else
2169
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
2156
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
2170
2157
End If
2171
2158
2172
2159
json_Converted = ConvertToJson(JsonValue(json_Index, json_Index2D), Whitespace, json_CurrentIndentation + 2 )
@@ -2183,14 +2170,14 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2183
2170
json_Converted = vbNewLine & json_InnerIndentation & json_Converted
2184
2171
End If
2185
2172
2186
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
2173
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
2187
2174
Next json_Index2D
2188
2175
2189
2176
If json_PrettyPrint Then
2190
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
2177
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
2191
2178
End If
2192
2179
2193
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2180
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2194
2181
json_IsFirstItem2D = True
2195
2182
Else
2196
2183
' 1D Array
@@ -2208,15 +2195,15 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2208
2195
json_Converted = vbNewLine & json_Indentation & json_Converted
2209
2196
End If
2210
2197
2211
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
2198
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
2212
2199
End If
2213
2200
Next json_Index
2214
2201
End If
2215
2202
2216
2203
On Error GoTo 0
2217
2204
2218
2205
If json_PrettyPrint Then
2219
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
2206
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
2220
2207
2221
2208
If VBA.VarType(Whitespace) = VBA.vbString Then
2222
2209
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -2225,9 +2212,9 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2225
2212
End If
2226
2213
End If
2227
2214
2228
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2215
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2229
2216
2230
- ConvertToJson = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
2217
+ ConvertToJson = json_BufferToString(json_Buffer , json_BufferPosition)
2231
2218
2232
2219
' Dictionary or Collection
2233
2220
Case VBA.vbObject
@@ -2241,7 +2228,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2241
2228
2242
2229
' Dictionary
2243
2230
If VBA.TypeName(JsonValue) = "Dictionary" Then
2244
- json_BufferAppend json_buffer , "{" , json_BufferPosition, json_BufferLength
2231
+ json_BufferAppend json_Buffer , "{" , json_BufferPosition, json_BufferLength
2245
2232
For Each json_Key In JsonValue.Keys
2246
2233
' For Objects, undefined (Empty/Nothing) is not added to object
2247
2234
json_Converted = ConvertToJson(JsonValue(json_Key), Whitespace, json_CurrentIndentation + 1 )
@@ -2255,7 +2242,7 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2255
2242
If json_IsFirstItem Then
2256
2243
json_IsFirstItem = False
2257
2244
Else
2258
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
2245
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
2259
2246
End If
2260
2247
2261
2248
If json_PrettyPrint Then
@@ -2264,12 +2251,12 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2264
2251
json_Converted = """" & json_Key & """:" & json_Converted
2265
2252
End If
2266
2253
2267
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
2254
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
2268
2255
End If
2269
2256
Next json_Key
2270
2257
2271
2258
If json_PrettyPrint Then
2272
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
2259
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
2273
2260
2274
2261
If VBA.VarType(Whitespace) = VBA.vbString Then
2275
2262
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -2278,16 +2265,16 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2278
2265
End If
2279
2266
End If
2280
2267
2281
- json_BufferAppend json_buffer , json_Indentation & "}" , json_BufferPosition, json_BufferLength
2268
+ json_BufferAppend json_Buffer , json_Indentation & "}" , json_BufferPosition, json_BufferLength
2282
2269
2283
2270
' Collection
2284
2271
ElseIf VBA.TypeName(JsonValue) = "Collection" Then
2285
- json_BufferAppend json_buffer , "[" , json_BufferPosition, json_BufferLength
2272
+ json_BufferAppend json_Buffer , "[" , json_BufferPosition, json_BufferLength
2286
2273
For Each json_Value In JsonValue
2287
2274
If json_IsFirstItem Then
2288
2275
json_IsFirstItem = False
2289
2276
Else
2290
- json_BufferAppend json_buffer , "," , json_BufferPosition, json_BufferLength
2277
+ json_BufferAppend json_Buffer , "," , json_BufferPosition, json_BufferLength
2291
2278
End If
2292
2279
2293
2280
json_Converted = ConvertToJson(json_Value, Whitespace, json_CurrentIndentation + 1 )
@@ -2304,11 +2291,11 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2304
2291
json_Converted = vbNewLine & json_Indentation & json_Converted
2305
2292
End If
2306
2293
2307
- json_BufferAppend json_buffer , json_Converted, json_BufferPosition, json_BufferLength
2294
+ json_BufferAppend json_Buffer , json_Converted, json_BufferPosition, json_BufferLength
2308
2295
Next json_Value
2309
2296
2310
2297
If json_PrettyPrint Then
2311
- json_BufferAppend json_buffer , vbNewLine, json_BufferPosition, json_BufferLength
2298
+ json_BufferAppend json_Buffer , vbNewLine, json_BufferPosition, json_BufferLength
2312
2299
2313
2300
If VBA.VarType(Whitespace) = VBA.vbString Then
2314
2301
json_Indentation = VBA.String $(json_CurrentIndentation, Whitespace)
@@ -2317,10 +2304,10 @@ Public Function ConvertToJson(ByVal JsonValue As Variant, Optional ByVal Whitesp
2317
2304
End If
2318
2305
End If
2319
2306
2320
- json_BufferAppend json_buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2307
+ json_BufferAppend json_Buffer , json_Indentation & "]" , json_BufferPosition, json_BufferLength
2321
2308
End If
2322
2309
2323
- ConvertToJson = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
2310
+ ConvertToJson = json_BufferToString(json_Buffer , json_BufferPosition)
2324
2311
Case VBA.vbInteger, VBA.vbLong, VBA.vbSingle, VBA.vbDouble, VBA.vbCurrency, VBA.vbDecimal
2325
2312
' Number (use decimals for numbers)
2326
2313
ConvertToJson = VBA.Replace(JsonValue, "," , "." )
@@ -2424,7 +2411,7 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
2424
2411
Dim json_Quote As String
2425
2412
Dim json_Char As String
2426
2413
Dim json_Code As String
2427
- Dim json_buffer As String
2414
+ Dim json_Buffer As String
2428
2415
Dim json_BufferPosition As Long
2429
2416
Dim json_BufferLength As Long
2430
2417
@@ -2445,36 +2432,36 @@ Private Function json_ParseString(json_String As String, ByRef json_Index As Lon
2445
2432
2446
2433
Select Case json_Char
2447
2434
Case """" , "\" , "/" , "'"
2448
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
2435
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
2449
2436
json_Index = json_Index + 1
2450
2437
Case "b"
2451
- json_BufferAppend json_buffer , vbBack, json_BufferPosition, json_BufferLength
2438
+ json_BufferAppend json_Buffer , vbBack, json_BufferPosition, json_BufferLength
2452
2439
json_Index = json_Index + 1
2453
2440
Case "f"
2454
- json_BufferAppend json_buffer , vbFormFeed, json_BufferPosition, json_BufferLength
2441
+ json_BufferAppend json_Buffer , vbFormFeed, json_BufferPosition, json_BufferLength
2455
2442
json_Index = json_Index + 1
2456
2443
Case "n"
2457
- json_BufferAppend json_buffer , vbCrLf, json_BufferPosition, json_BufferLength
2444
+ json_BufferAppend json_Buffer , vbCrLf, json_BufferPosition, json_BufferLength
2458
2445
json_Index = json_Index + 1
2459
2446
Case "r"
2460
- json_BufferAppend json_buffer , vbCr, json_BufferPosition, json_BufferLength
2447
+ json_BufferAppend json_Buffer , vbCr, json_BufferPosition, json_BufferLength
2461
2448
json_Index = json_Index + 1
2462
2449
Case "t"
2463
- json_BufferAppend json_buffer , vbTab, json_BufferPosition, json_BufferLength
2450
+ json_BufferAppend json_Buffer , vbTab, json_BufferPosition, json_BufferLength
2464
2451
json_Index = json_Index + 1
2465
2452
Case "u"
2466
2453
' Unicode character escape (e.g. \u00a9 = Copyright)
2467
2454
json_Index = json_Index + 1
2468
2455
json_Code = VBA.Mid$(json_String, json_Index, 4 )
2469
- json_BufferAppend json_buffer , VBA.ChrW(VBA.Val("&h" + json_Code)), json_BufferPosition, json_BufferLength
2456
+ json_BufferAppend json_Buffer , VBA.ChrW(VBA.Val("&h" + json_Code)), json_BufferPosition, json_BufferLength
2470
2457
json_Index = json_Index + 4
2471
2458
End Select
2472
2459
Case json_Quote
2473
- json_ParseString = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
2460
+ json_ParseString = json_BufferToString(json_Buffer , json_BufferPosition)
2474
2461
json_Index = json_Index + 1
2475
2462
Exit Function
2476
2463
Case Else
2477
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
2464
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
2478
2465
json_Index = json_Index + 1
2479
2466
End Select
2480
2467
Loop
@@ -2560,7 +2547,7 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
2560
2547
Dim json_Index As Long
2561
2548
Dim json_Char As String
2562
2549
Dim json_AscCode As Long
2563
- Dim json_buffer As String
2550
+ Dim json_Buffer As String
2564
2551
Dim json_BufferPosition As Long
2565
2552
Dim json_BufferLength As Long
2566
2553
@@ -2609,10 +2596,10 @@ Private Function json_Encode(ByVal json_Text As Variant) As String
2609
2596
json_Char = "\u" & VBA.Right$("0000" & VBA.Hex$(json_AscCode), 4 )
2610
2597
End Select
2611
2598
2612
- json_BufferAppend json_buffer , json_Char, json_BufferPosition, json_BufferLength
2599
+ json_BufferAppend json_Buffer , json_Char, json_BufferPosition, json_BufferLength
2613
2600
Next json_Index
2614
2601
2615
- json_Encode = json_BufferToString(json_buffer , json_BufferPosition, json_BufferLength )
2602
+ json_Encode = json_BufferToString(json_Buffer , json_BufferPosition)
2616
2603
End Function
2617
2604
2618
2605
Private Function json_Peek (json_String As String , ByVal json_Index As Long , Optional json_NumberOfCharacters As Long = 1 ) As String
@@ -2639,7 +2626,6 @@ Private Function json_StringIsLargeNumber(json_String As Variant) As Boolean
2639
2626
' Length with be at least 16 characters and assume will be less than 100 characters
2640
2627
If json_Length >= 16 And json_Length <= 100 Then
2641
2628
Dim json_CharCode As String
2642
- Dim json_Index As Long
2643
2629
2644
2630
json_StringIsLargeNumber = True
2645
2631
@@ -2685,13 +2671,10 @@ Private Function json_ParseErrorMessage(json_String As String, ByRef json_Index
2685
2671
ErrorMessage
2686
2672
End Function
2687
2673
2688
- Private Sub json_BufferAppend (ByRef json_buffer As String , _
2674
+ Private Sub json_BufferAppend (ByRef json_Buffer As String , _
2689
2675
ByRef json_Append As Variant , _
2690
2676
ByRef json_BufferPosition As Long , _
2691
2677
ByRef json_BufferLength As Long )
2692
- #If Mac Then
2693
- json_buffer = json_buffer & json_Append
2694
- #Else
2695
2678
' VBA can be slow to append strings due to allocating a new string for each append
2696
2679
' Instead of using the traditional append, allocate a large empty string and then copy string at append position
2697
2680
'
@@ -2705,71 +2688,40 @@ Private Sub json_BufferAppend(ByRef json_buffer As String, _
2705
2688
' Buffer: "abc "
2706
2689
' Buffer Length: 10
2707
2690
'
2708
- ' Copy memory for "def" into buffer at position 3 (0-based)
2691
+ ' Put "def" into buffer at position 3 (0-based)
2709
2692
' Buffer: "abcdef "
2710
2693
'
2711
2694
' Approach based on cStringBuilder from vbAccelerator
2712
2695
' http://www.vbaccelerator.com/home/VB/Code/Techniques/RunTime_Debug_Tracing/VB6_Tracer_Utility_zip_cStringBuilder_cls.asp
2696
+ '
2697
+ ' and clsStringAppend from Philip Swannell
2698
+ ' https://github.com/VBA-tools/VBA-JSON/pull/82
2713
2699
2714
2700
Dim json_AppendLength As Long
2715
2701
Dim json_LengthPlusPosition As Long
2716
2702
2717
- json_AppendLength = VBA.LenB (json_Append)
2703
+ json_AppendLength = VBA.Len (json_Append)
2718
2704
json_LengthPlusPosition = json_AppendLength + json_BufferPosition
2719
2705
2720
2706
If json_LengthPlusPosition > json_BufferLength Then
2721
- ' Appending would overflow buffer, add chunks until buffer is long enough
2722
- Dim json_TemporaryLength As Long
2723
-
2724
- json_TemporaryLength = json_BufferLength
2725
- Do While json_TemporaryLength < json_LengthPlusPosition
2726
- ' Initially, initialize string with 255 characters,
2727
- ' then add large chunks (8192) after that
2728
- '
2729
- ' Size: # Characters x 2 bytes / character
2730
- If json_TemporaryLength = 0 Then
2731
- json_TemporaryLength = json_TemporaryLength + 510
2732
- Else
2733
- json_TemporaryLength = json_TemporaryLength + 16384
2734
- End If
2735
- Loop
2707
+ ' Appending would overflow buffer, add chunk
2708
+ ' (double buffer length or append length, whichever is bigger)
2709
+ Dim json_AddedLength As Long
2710
+ json_AddedLength = IIf (json_AppendLength > json_BufferLength, json_AppendLength, json_BufferLength)
2736
2711
2737
- json_buffer = json_buffer & VBA.Space$((json_TemporaryLength - json_BufferLength) \ 2 )
2738
- json_BufferLength = json_TemporaryLength
2712
+ json_Buffer = json_Buffer & VBA.Space$(json_AddedLength )
2713
+ json_BufferLength = json_BufferLength + json_AddedLength
2739
2714
End If
2740
2715
2741
- ' Copy memory from append to buffer at buffer position
2742
- json_CopyMemory ByVal json_UnsignedAdd(StrPtr(json_buffer), _
2743
- json_BufferPosition), _
2744
- ByVal StrPtr(json_Append), _
2745
- json_AppendLength
2746
-
2716
+ ' Note: Namespacing with VBA.Mid$ doesn't work properly here, throwing compile error:
2717
+ ' Function call on left-hand side of assignment must return Variant or Object
2718
+ Mid$(json_Buffer, json_BufferPosition + 1 , json_AppendLength) = CStr(json_Append)
2747
2719
json_BufferPosition = json_BufferPosition + json_AppendLength
2748
- #End If
2749
2720
End Sub
2750
2721
2751
- Private Function json_BufferToString (ByRef json_buffer As String , ByVal json_BufferPosition As Long , ByVal json_BufferLength As Long ) As String
2752
- #If Mac Then
2753
- json_BufferToString = json_buffer
2754
- #Else
2722
+ Private Function json_BufferToString (ByRef json_Buffer As String , ByVal json_BufferPosition As Long ) As String
2755
2723
If json_BufferPosition > 0 Then
2756
- json_BufferToString = VBA.Left$(json_buffer, json_BufferPosition \ 2 )
2757
- End If
2758
- #End If
2759
- End Function
2760
-
2761
- #If VBA7 Then
2762
- Private Function json_UnsignedAdd (json_Start As LongPtr , json_Increment As Long ) As LongPtr
2763
- #Else
2764
- Private Function json_UnsignedAdd (json_Start As Long , json_Increment As Long ) As Long
2765
- #End If
2766
-
2767
- If json_Start And &H80000000 Then
2768
- json_UnsignedAdd = json_Start + json_Increment
2769
- ElseIf (json_Start Or &H80000000 ) < -json_Increment Then
2770
- json_UnsignedAdd = json_Start + json_Increment
2771
- Else
2772
- json_UnsignedAdd = (json_Start + &H80000000 ) + (json_Increment + &H80000000 )
2724
+ json_BufferToString = VBA.Left$(json_Buffer, json_BufferPosition)
2773
2725
End If
2774
2726
End Function
2775
2727
0 commit comments