Skip to content

Commit

Permalink
Handle duplicate keys when parsing json
Browse files Browse the repository at this point in the history
  • Loading branch information
timhall committed Dec 3, 2013
1 parent 640b3e1 commit 666eecd
Show file tree
Hide file tree
Showing 12 changed files with 29 additions and 15 deletions.
Binary file modified Excel-REST - Blank.xlsm
Binary file not shown.
1 change: 1 addition & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ For more details, check out the [Wiki](https://github.com/timhall/Excel-REST/wik
- Add RestClientBase for future use with extension for single-client applications
- Add build scripts for import/export
- New specs and bugfixes
- __v2.0.1__ Handle duplicate keys when parsing json

#### v1.1.0

Expand Down
2 changes: 1 addition & 1 deletion build/import.vbs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ Else
End If

' Include all standard Excel-REST modules
Modules = Array("RestHelpers.bas", "IAuthenticator.cls", "RestClient.cls", "RestRequest.cls", "RestResponse.cls")
Modules = Array("RestHelpers.bas", "IAuthenticator.cls", "RestClient.cls", "RestRequest.cls", "RestResponse.cls", "RestClientBase.bas")

' Open Excel
KeepExcelOpen = OpenExcel(Excel)
Expand Down
Binary file modified examples/Excel-REST - Example.xlsm
Binary file not shown.
Binary file modified specs/Excel-REST - Specs.xlsm
Binary file not shown.
10 changes: 10 additions & 0 deletions specs/RestHelpersSpecs.bas
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,16 @@ Public Function Specs() As SpecSuite
End If
End With

With Specs.It("should overwrite parsed json for duplicate keys")
json = "{""a"":1,""a"":2,""a"":3}"
Set Parsed = RestHelpers.ParseJSON(json)

.Expect(Parsed).ToBeDefined
If Not Parsed Is Nothing Then
.Expect(Parsed("a")).ToEqual 3
End If
End With

With Specs.It("should convert to json")
Set Obj = CreateObject("Scripting.Dictionary")
Obj.Add "a", 1
Expand Down
2 changes: 1 addition & 1 deletion src/IAuthenticator.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' IAuthenticator v2.0.0
' IAuthenticator v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Interface for creating authenticators for rest client
Expand Down
4 changes: 2 additions & 2 deletions src/RestClient.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestClient v2.0.0
' RestClient v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Interact with REST web services from Excel
Expand All @@ -19,7 +19,7 @@ Attribute VB_Exposed = True
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Option Explicit

Private Const UserAgent As String = "Excel Client v2.0.0 (https://github.com/timhall/Excel-REST)"
Private Const UserAgent As String = "Excel Client v2.0.1 (https://github.com/timhall/Excel-REST)"
Private Const DefaultTimeoutMS As Integer = 5000


Expand Down
4 changes: 2 additions & 2 deletions src/RestClientBase.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "RestClientBase"
''
' RestClientBase v2.0.0
' RestClientBase v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Extendable RestClientBase for developing custom client classes
Expand All @@ -15,7 +15,7 @@ Attribute VB_Name = "RestClientBase"
' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
Option Explicit

Private Const UserAgent As String = "Excel Client v2.0.0 (https://github.com/timhall/Excel-REST)"
Private Const UserAgent As String = "Excel Client v2.0.1 (https://github.com/timhall/Excel-REST)"
Private Const TimeoutMS As Integer = 5000
Private Initialized As Boolean

Expand Down
17 changes: 10 additions & 7 deletions src/RestHelpers.bas
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Attribute VB_Name = "RestHelpers"
''
' RestHelpers v2.0.0
' RestHelpers v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Common helpers RestClient
Expand Down Expand Up @@ -398,6 +398,7 @@ End Function
' - Updated json_parseNumber to reduce chance of overflow
' - Swapped Mid for Mid$
' - Handle colon in object key
' - Handle duplicate keys in object parsing
' - Change methods to Private and prefix with json_
'
' ======================================================================================== '
Expand Down Expand Up @@ -442,8 +443,9 @@ Private Function json_parseObject(ByRef str As String, ByRef index As Long) As O
If Mid$(str, index, 1) <> "{" Then Err.Raise vbObjectError + INVALID_OBJECT, Description:="char " & index & " : " & Mid$(str, index)
index = index + 1

Do
Dim Key As String

Do
Call json_skipChar(str, index)
If "}" = Mid$(str, index, 1) Then
index = index + 1
Expand All @@ -453,11 +455,12 @@ Private Function json_parseObject(ByRef str As String, ByRef index As Long) As O
Call json_skipChar(str, index)
End If

Dim Key As String

' add key/value pair
json_parseObject.Add Key:=json_parseKey(str, index), Item:=json_parseValue(str, index)

Key = json_parseKey(str, index)
If Not json_parseObject.Exists(Key) Then
json_parseObject.Add Key, json_parseValue(str, index)
Else
json_parseObject.Item(Key) = json_parseValue(str, index)
End If
Loop

End Function
Expand Down
2 changes: 1 addition & 1 deletion src/RestRequest.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestRequest v2.0.0
' RestRequest v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Create a request for use with a rest client
Expand Down
2 changes: 1 addition & 1 deletion src/RestResponse.cls
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Attribute VB_Creatable = False
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
''
' RestResponse v2.0.0
' RestResponse v2.0.1
' (c) Tim Hall - https://github.com/timhall/Excel-REST
'
' Wrapper for http responses
Expand Down

0 comments on commit 666eecd

Please sign in to comment.