Rajdeep
Rajdeep

Reputation: 802

How to convert JSON data to xml data in excel macro or VB.Net

I am getting data in JSON format

{"name":"ryan","age":1,"roll":2,"address":"aaa"},{"name":"ryan","age":1,"roll":2,"address":"aaa"},{"name":"ryan","age":1,"roll":2,"address":"aaa"},{"name":"ryan","age":1,"roll":2,"address":"aaa"}]

How can it be converted into xml format. So that i can use it in populating my excel spreadsheet. Or is there any way to directly convert JSON data to excel in macro

Upvotes: 0

Views: 8448

Answers (3)

omegastripes
omegastripes

Reputation: 12612

Consider this example:

Option Explicit

Sub JsonPopulateCellsTest()
    Dim strJsonString As String
    Dim varJson As Variant
    Dim strState As String
    Dim i As Long
    Dim y As Long

    ' parse JSON string
    strJsonString = "[{""name"":""ryan"",""age"":1,""roll"":2,""address"":""aaa""},{""name"":""ryna"",""age"":2,""roll"":3,""address"":""bbb""},{""name"":""yran"",""age"":5,""roll"":3,""address"":""ccc""},{""name"":""yrna"",""age"":20,""roll"":4,""address"":""ddd""}]"
    ParseJson strJsonString, varJson, strState
    If strState = "Error" Then
        MsgBox "Error"
        Exit Sub
    End If

    ' show the full structure starting from root element
    MsgBox BeautifyJson(varJson)

    y = 1 ' begin row

    ' output
    For i = 0 To UBound(varJson)
        Cells(y + i, 1).Value = varJson(i)("name")
        Cells(y + i, 2).Value = varJson(i)("age")
        Cells(y + i, 3).Value = varJson(i)("roll")
        Cells(y + i, 4).Value = varJson(i)("address")
    Next

End Sub

Sub ParseJson(ByVal strContent As String, varJson As Variant, strState As String)
    ' strContent - source JSON string
    ' varJson - created object or array to be returned as result
    ' strState - Object|Array|Error depending on processing to be returned as state
    Dim objTokens As Object
    Dim lngTokenId As Long
    Dim objRegEx As Object
    Dim bMatched As Boolean

    Set objTokens = CreateObject("Scripting.Dictionary")
    lngTokenId = 0
    Set objRegEx = CreateObject("VBScript.RegExp")
    With objRegEx
        ' specification http://www.json.org/
        .Global = True
        .MultiLine = True
        .IgnoreCase = True
        .Pattern = """(?:\\""|[^""])*""(?=\s*(?:,|\:|\]|\}))"
        Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "str"
        .Pattern = "(?:[+-])?(?:\d+\.\d*|\.\d+|\d+)e(?:[+-])?\d+(?=\s*(?:,|\]|\}))"
        Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "num"
        .Pattern = "(?:[+-])?(?:\d+\.\d*|\.\d+|\d+)(?=\s*(?:,|\]|\}))"
        Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "num"
        .Pattern = "\b(?:true|false|null)(?=\s*(?:,|\]|\}))"
        Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "cst"
        .Pattern = "\b[A-Za-z_]\w*(?=\s*\:)" ' unspecified name without quotes
        Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "nam"
        .Pattern = "\s"
        strContent = .Replace(strContent, "")
        .MultiLine = False
        Do
            bMatched = False
            .Pattern = "<\d+(?:str|nam)>\:<\d+(?:str|num|obj|arr|cst)>"
            Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "prp"
            .Pattern = "\{(?:<\d+prp>(?:,<\d+prp>)*)?\}"
            Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "obj"
            .Pattern = "\[(?:<\d+(?:str|num|obj|arr|cst)>(?:,<\d+(?:str|num|obj|arr|cst)>)*)?\]"
            Tokenize objTokens, objRegEx, strContent, lngTokenId, bMatched, "arr"
        Loop While bMatched
        .Pattern = "^<\d+(?:obj|arr)>$" ' unspecified top level array
        If Not (.test(strContent) And objTokens.Exists(strContent)) Then
            varJson = Null
            strState = "Error"
        Else
            Retrieve objTokens, objRegEx, strContent, varJson
            strState = IIf(IsObject(varJson), "Object", "Array")
        End If
    End With
End Sub

Sub Tokenize(objTokens, objRegEx, strContent, lngTokenId, bMatched, strType)
    Dim strKey As String
    Dim strRes As String
    Dim lngCopyIndex As Long
    Dim objMatch As Object

    strRes = ""
    lngCopyIndex = 1
    With objRegEx
        For Each objMatch In .Execute(strContent)
            strKey = "<" & lngTokenId & strType & ">"
            bMatched = True
            With objMatch
                objTokens(strKey) = .Value
                strRes = strRes & Mid(strContent, lngCopyIndex, .FirstIndex - lngCopyIndex + 1) & strKey
                lngCopyIndex = .FirstIndex + .Length + 1
            End With
            lngTokenId = lngTokenId + 1
        Next
        strContent = strRes & Mid(strContent, lngCopyIndex, Len(strContent) - lngCopyIndex + 1)
    End With
End Sub

Sub Retrieve(objTokens, objRegEx, strTokenKey, varTransfer)
    Dim strContent As String
    Dim strType As String
    Dim objMatches As Object
    Dim objMatch As Object
    Dim strName As String
    Dim varValue As Variant
    Dim objArrayElts As Object

    strType = Left(Right(strTokenKey, 4), 3)
    strContent = objTokens(strTokenKey)
    With objRegEx
        .Global = True
        Select Case strType
            Case "obj"
                .Pattern = "<\d+\w{3}>"
                Set objMatches = .Execute(strContent)
                Set varTransfer = CreateObject("Scripting.Dictionary")
                For Each objMatch In objMatches
                    Retrieve objTokens, objRegEx, objMatch.Value, varTransfer
                Next
            Case "prp"
                .Pattern = "<\d+\w{3}>"
                Set objMatches = .Execute(strContent)

                Retrieve objTokens, objRegEx, objMatches(0).Value, strName
                Retrieve objTokens, objRegEx, objMatches(1).Value, varValue
                If IsObject(varValue) Then
                    Set varTransfer(strName) = varValue
                Else
                    varTransfer(strName) = varValue
                End If
            Case "arr"
                .Pattern = "<\d+\w{3}>"
                Set objMatches = .Execute(strContent)
                Set objArrayElts = CreateObject("Scripting.Dictionary")
                For Each objMatch In objMatches
                    Retrieve objTokens, objRegEx, objMatch.Value, varValue
                    If IsObject(varValue) Then
                        Set objArrayElts(objArrayElts.Count) = varValue
                    Else
                        objArrayElts(objArrayElts.Count) = varValue
                    End If
                    varTransfer = objArrayElts.Items
                Next
            Case "nam"
                varTransfer = strContent
            Case "str"
                varTransfer = Mid(strContent, 2, Len(strContent) - 2)
                varTransfer = Replace(varTransfer, "\""", """")
                varTransfer = Replace(varTransfer, "\\", "\")
                varTransfer = Replace(varTransfer, "\/", "/")
                varTransfer = Replace(varTransfer, "\b", Chr(8))
                varTransfer = Replace(varTransfer, "\f", Chr(12))
                varTransfer = Replace(varTransfer, "\n", vbLf)
                varTransfer = Replace(varTransfer, "\r", vbCr)
                varTransfer = Replace(varTransfer, "\t", vbTab)
                .Global = False
                .Pattern = "\\u[0-9a-fA-F]{4}"
                Do While .test(varTransfer)
                    varTransfer = .Replace(varTransfer, ChrW(("&H" & Right(.Execute(varTransfer)(0).Value, 4)) * 1))
                Loop
            Case "num"
                varTransfer = Evaluate(strContent)
            Case "cst"
                Select Case LCase(strContent)
                    Case "true"
                        varTransfer = True
                    Case "false"
                        varTransfer = False
                    Case "null"
                        varTransfer = Null
                End Select
        End Select
    End With
End Sub

Function BeautifyJson(varJson As Variant) As String
    Dim strResult As String
    Dim lngIndent As Long
    BeautifyJson = ""
    lngIndent = 0
    BeautyTraverse BeautifyJson, lngIndent, varJson, vbTab, 1
End Function

Sub BeautyTraverse(strResult As String, lngIndent As Long, varElement As Variant, strIndent As String, lngStep As Long)
    Dim arrKeys() As Variant
    Dim lngIndex As Long
    Dim strTemp As String

    Select Case VarType(varElement)
        Case vbObject
            If varElement.Count = 0 Then
                strResult = strResult & "{}"
            Else
                strResult = strResult & "{" & vbCrLf
                lngIndent = lngIndent + lngStep
                arrKeys = varElement.Keys
                For lngIndex = 0 To UBound(arrKeys)
                    strResult = strResult & String(lngIndent, strIndent) & """" & arrKeys(lngIndex) & """" & ": "
                    BeautyTraverse strResult, lngIndent, varElement(arrKeys(lngIndex)), strIndent, lngStep
                    If Not (lngIndex = UBound(arrKeys)) Then strResult = strResult & ","
                    strResult = strResult & vbCrLf
                Next
                lngIndent = lngIndent - lngStep
                strResult = strResult & String(lngIndent, strIndent) & "}"
            End If
        Case Is >= vbArray
            If UBound(varElement) = -1 Then
                strResult = strResult & "[]"
            Else
                strResult = strResult & "[" & vbCrLf
                lngIndent = lngIndent + lngStep
                For lngIndex = 0 To UBound(varElement)
                    strResult = strResult & String(lngIndent, strIndent)
                    BeautyTraverse strResult, lngIndent, varElement(lngIndex), strIndent, lngStep
                    If Not (lngIndex = UBound(varElement)) Then strResult = strResult & ","
                    strResult = strResult & vbCrLf
                Next
                lngIndent = lngIndent - lngStep
                strResult = strResult & String(lngIndent, strIndent) & "]"
            End If
        Case vbInteger, vbLong, vbSingle, vbDouble
            strResult = strResult & varElement
        Case vbNull
            strResult = strResult & "Null"
        Case vbBoolean
            strResult = strResult & IIf(varElement, "True", "False")
        Case Else
            strTemp = Replace(varElement, "\""", """")
            strTemp = Replace(strTemp, "\", "\\")
            strTemp = Replace(strTemp, "/", "\/")
            strTemp = Replace(strTemp, Chr(8), "\b")
            strTemp = Replace(strTemp, Chr(12), "\f")
            strTemp = Replace(strTemp, vbLf, "\n")
            strTemp = Replace(strTemp, vbCr, "\r")
            strTemp = Replace(strTemp, vbTab, "\t")
            strResult = strResult & """" & strTemp & """"
    End Select

End Sub

Upvotes: 0

Excel Hero
Excel Hero

Reputation: 14764

Or is there any way to directly convert JSON data to excel in macro?

Sometimes JSON text is very complex and in those cases it is best to use a JSON parsing library to get at the data.

However, sometimes the data simply represent a 2D table of data and this appears to be the case with your JSON text.

In the latter case, the data can be written to a worksheet by way of simple VBA processing.

Place the following routines in a standard code module:

Public Sub JsonTable2Range(rOut As Range, json As String)
    Dim i&, j&, p1&, p2&, sRow$, cols, v, vp
    i = 1
    p1 = 1
    Do
        p1 = InStr(p1, json, "{"): If p1 = 0 Then Exit Do
        p2 = InStr(p1, json, "}")
        sRow = Mid$(json, p1 + 1, p2 - p1 - 1)
        cols = Split(sRow, ",")
        If i = 1 Then
            ReDim v(0 To UBound(Split(json, "}")) + 1, 0 To UBound(cols) + 1)
            For j = 0 To UBound(cols)
                vp = Split(cols(j), ":")
                v(0, j) = ProcessValuePair(vp, 0)
            Next
        End If
        For j = 0 To UBound(cols)
            vp = Split(cols(j), ":")
            v(i, j) = ProcessValuePair(vp, 1)
        Next
        i = i + 1
        p1 = p1 + 1
    DoEvents
    Loop
    If i > 1 Then rOut.Resize(UBound(v), UBound(v, 2)) = v
End Sub

Private Function ProcessValuePair(vp, n)
    If Asc(Mid$(vp(n), 1, 1)) = 10 Then vp(n) = Mid$(vp(n), 2)
    vp(n) = Trim$(vp(n))
    If Left$(vp(n), 1) = "'" Or Left$(vp(n), 1) = """" Then
        vp(n) = Mid$(vp(n), 2, Len(vp(n)) - 2)
    Else
        vp(n) = Val(vp(n))
    End If
    ProcessValuePair = vp(n)
End Function

Here is how to use the above...

If you have the JSON text already in a VBA variable (perhaps that variable is called sJSON) then to parse sJSON to the active worksheet beginning in cell A1, do this:

JsonTable2Range [a1], sJSON

On the other hand, if you have the JSON text in cell A1 on Sheet2 and you'd like for the parsing to output to cell A1 on Sheet1, do this:

JsonTable2Range [sheet1!a1], [sheet2!a1]

Upvotes: 1

C.Laetitia
C.Laetitia

Reputation: 11

Your questions has been already ask on stackoverflow. Please follow this one: Convert JSON to Array OR JSON to XML in VB.NET ONLY

you may have a look at this link also. http://www.newtonsoft.com/json/help/html/convertingjsonandxml.htm

Upvotes: 0

Related Questions