Consulting

Results 1 to 2 of 2

Thread: VBA AND XML

  1. #1
    VBAX Regular
    Joined
    May 2012
    Posts
    15
    Location

    VBA AND XML

    Hi guys,

    I have a question about VBA and XML.

    All I’m trying to do (very simple) is to extract the weather from a XML page. I have tried doing this with stock quotes from yahoo using yql and it works really well and is very easy to get what i need.

    So all I want to do is to access the 15.1 in the below XML code (<b>Temperature:</b> 15.1°) but i don’t know how to do this because of <![CDATA[ is in the way and how I am doing this currently is trimming the contents within the XML description tag but obviously this is a really bad idea when the spacing changes in the website.

    Does anyone know how I can access the weather of 15.1 degress within <![CDATA[ ?????

    Note: for the URLS (http) was removed.

    Thanks.

    ‘’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’ ’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’ ’’’’’’’’’’’’
    Sub testw()
    Dim xml As Object
    Dim response As String
    Dim URL As String
    Dim bb As String

    URL = "rss.weatherzone.com.au/?u=12994-1285&lt=aploc&lc=5594&obs=1&fc=1&warn=1"

    Set xml = CreateObject("MSXML2.XMLHTTP.5.0")

    With xml
    .Open "GET", URL, False
    .send
    End With

    ‘response = xml.responseXML.xml
    ‘MsgBox response

    On Error Resume Next
    URL = Left(xml.responseXML.SelectNodes("//description").Item(1).Text, 33)
    bb = Right(URL, 5)
    msgbox "Melb. " & bb & "°C"
    end sub
    ‘’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’ ’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’’ ’’’’’’’’’’’’
    <description><![CDATA[
    <b>Temperature:</b> 15.1°C[/COLOR]
    <img align="top" src="weatherzone.com.au/images/widgets/nav_trend_down.gif" alt="falling"/>
    <br />
    <b>Feels like:</b> 15.1°C<br />
    <b>Dew point:</b> 2.8°C
    <img align="top" src="weatherzone.com.au/images/widgets/nav_trend_up.gif" alt="rising"/>
    <br />
    <b>Relative humidity:</b> 44%<br />
    <b>Wind:</b> NW at 28 km/h, gusting to 37 km/h
    <img align="top" src="weatherzone.com.au/images/widgets/nav_trend_down.gif" alt="falling"/>
    <br />
    <b>Rain:</b> 0.0mm since 9am<br />
    <b>Pressure:</b> 1020.3 hPa
    <img align="top" src="weatherzone.com.au/images/widgets/nav_trend_steady.gif" alt="steady"/>
    <br />
    ]]></description>

  2. #2
    VBAX Mentor Teeroy's Avatar
    Joined
    Apr 2012
    Location
    Sydney, Australia
    Posts
    414
    Location
    It's not quite as simple as it appeared, but a fun challenge. I found it better to pass the HttpRequest to a DOM to work through the XML with a recursive function (which as I've said to others before hurt my brain ).

    The following will find the data after the first insance of "Temperature:" and write the info you want to a msgbox but you can alter as you like.

    Don't forget to create a Reference to Microsoft XML, v6.0 in your VBE.

    [VBA]
    Sub test()
    Dim xDOC As DOMDocument
    Dim XMLHttpRequest As XMLHTTP
    Dim response As String
    Dim URL As String
    Dim sTemperature As String

    URL = "http://rss.weatherzone.com.au/?u=12994-1285&lt=aploc&lc=5594&obs=1&fc=1&warn=1"

    Set XMLHttpRequest = New MSXML2.XMLHTTP
    With XMLHttpRequest
    .Open "GET", URL, False
    .send
    End With

    Set xDOC = New DOMDocument

    Do Until xDOC.readyState = 4
    Loop
    xDOC.loadXML (XMLHttpRequest.responseText)

    sTemperature = DisplayNode(xDOC.childNodes)

    On Error Resume Next

    MsgBox "Melb. " & sTemperature & " °C"
    End Sub

    Public Function DisplayNode(ByRef Nodes As IXMLDOMNodeList)

    Dim xNode As IXMLDOMNode
    Dim Start As String
    Dim Finish As String
    Dim Output As String


    For Each xNode In Nodes
    If xNode.NodeType = NODE_CDATA_SECTION And _
    InStr(xNode.NodeValue, "Temperature:") <> 0 Then
    Start = InStr(xNode.NodeValue, "Temperature:") + 17
    Finish = InStr(xNode.NodeValue, Chr(35)) - 1
    DisplayNode = Mid(xNode.NodeValue, Start, Finish - Start)
    End If
    If DisplayNode <> "" Then Exit Function
    If xNode.HasChildNodes Then
    Output = DisplayNode(xNode.childNodes)
    If Output <> "" Then DisplayNode = Output
    End If
    Next xNode
    End Function
    [/VBA]
    _________________________________________________________________________
    "In theory there is no difference between theory and practice. In practice there is." - Chuck Reid

    Any day you learn something new is a day not wasted.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •