Zoeken…


Invoering

Als u de objecten in andere toepassingen gebruikt als onderdeel van uw Visual Basic-toepassing, wilt u mogelijk een verwijzing naar de objectbibliotheken van die toepassingen maken. Deze documentatie biedt een lijst, bronnen en voorbeelden van het gebruik van bibliotheken van verschillende software, zoals Windows Shell, Internet Explorer, XML HttpRequest en andere.

Syntaxis

  • expression.CreateObject (ObjectName)
  • uitdrukking; Verplicht. Een uitdrukking die een toepassingsobject retourneert.
  • ObjectName; Vereiste string. De klassenaam van het object dat moet worden gemaakt. Zie OLE Programmatic Identifiers voor informatie over geldige klassenamen.

Opmerkingen

Wanneer een toepassing automatisering ondersteunt, kunnen de objecten die de toepassing blootstelt worden benaderd door Visual Basic. Gebruik Visual Basic om deze objecten te manipuleren door methoden op het object aan te roepen of door de eigenschappen van het object op te halen en in te stellen.

Als u de objecten in andere toepassingen gebruikt als onderdeel van uw Visual Basic-toepassing, wilt u mogelijk een verwijzing naar de objectbibliotheken van die toepassingen maken. Voordat u dat kunt doen, moet u er eerst zeker van zijn dat de toepassing een objectbibliotheek biedt.

Hiermee kunt u de objecten van een andere applicatie selecteren die u in uw code beschikbaar wilt hebben door een verwijzing naar de objectbibliotheek van die applicatie in te stellen.

Maakt een automatiseringsobject van de opgegeven klasse. Als de toepassing al actief is, maakt CreateObject een nieuw exemplaar.

VBScript Reguliere uitdrukkingen

Set createVBScriptRegExObject = CreateObject("vbscript.RegExp")

Hulpmiddelen> Referenties> Microsoft VBScript Reguliere expressies #. #
Bijbehorende DLL: VBScript.dll
Bron: Internet Explorer 1.0 en 5.5

Code

U kunt deze functies gebruiken om RegEx-resultaten te krijgen, alle overeenkomsten (indien meer dan 1) samen te voegen in 1 string en het resultaat in Excel-cel weer te geven.

Public Function getRegExResult(ByVal SourceString As String, Optional ByVal RegExPattern As String = "\d+", _
    Optional ByVal isGlobalSearch As Boolean = True, Optional ByVal isCaseSensitive As Boolean = False, Optional ByVal Delimiter As String = ";") As String
    
    Static RegExObject As Object
    If RegExObject Is Nothing Then
        Set RegExObject = createVBScriptRegExObject
    End If
    
    getRegExResult = removeLeadingDelimiter(concatObjectItems(getRegExMatches(RegExObject, SourceString, RegExPattern, isGlobalSearch, isCaseSensitive), Delimiter), Delimiter)
    
End Function

Private Function getRegExMatches(ByRef RegExObj As Object, _
    ByVal SourceString As String, ByVal RegExPattern As String, ByVal isGlobalSearch As Boolean, ByVal isCaseSensitive As Boolean) As Object

    With RegExObj
        .Global = isGlobalSearch
        .IgnoreCase = Not (isCaseSensitive) 'it is more user friendly to use positive meaning of argument, like isCaseSensitive, than to use negative IgnoreCase
        .Pattern = RegExPattern
        Set getRegExMatches = .Execute(SourceString)
    End With
    
End Function

Private Function concatObjectItems(ByRef Obj As Object, Optional ByVal DelimiterCustom As String = ";") As String
    Dim ObjElement As Variant
    For Each ObjElement In Obj
        concatObjectItems = concatObjectItems & DelimiterCustom & ObjElement.Value
    Next
End Function

Public Function removeLeadingDelimiter(ByVal SourceString As String, ByVal Delimiter As String) As String
    If Left$(SourceString, Len(Delimiter)) = Delimiter Then
        removeLeadingDelimiter = Mid$(SourceString, Len(Delimiter) + 1)
    End If
End Function

Private Function createVBScriptRegExObject() As Object
    Set createVBScriptRegExObject = CreateObject("vbscript.RegExp") 'ex.: createVBScriptRegExObject.Pattern
End Function

Scriptbestandssysteemobject

Set createScriptingFileSystemObject = CreateObject("Scripting.FileSystemObject")

Hulpmiddelen> Referenties> Microsoft Scripting Runtime
Bijbehorende DLL: ScrRun.dll
Bron: Windows OS

MSDN-toegang tot bestanden met FileSystemObject

Het File System Object (FSO) -model biedt een objectgebaseerd hulpmiddel voor het werken met mappen en bestanden. Hiermee kunt u de bekende syntaxis object.method met een uitgebreide set eigenschappen, methoden en gebeurtenissen gebruiken om mappen en bestanden te verwerken. U kunt ook de traditionele Visual Basic-instructies en -opdrachten gebruiken.

Het FSO-model geeft uw toepassing de mogelijkheid om mappen te maken, wijzigen, verplaatsen en verwijderen, of om te bepalen of en waar bepaalde mappen bestaan. Hiermee kunt u ook informatie krijgen over mappen, zoals hun namen en de datum waarop ze zijn gemaakt of voor het laatst gewijzigd.

MSDN-FileSystemObject onderwerpen : " ... leg het concept van het FileSystemObject uit en hoe het te gebruiken. " Exceltrick-FileSystemObject in VBA - Uitgelegd
Scripting.FileSystemObject

Scripting Dictionary-object

Set dict = CreateObject("Scripting.Dictionary")

Hulpmiddelen> Referenties> Microsoft Scripting Runtime
Bijbehorende DLL: ScrRun.dll
Bron: Windows OS

Scripting.Dictionary object
MSDN-woordenboekobject

Internet Explorer-object

Set createInternetExplorerObject = CreateObject("InternetExplorer.Application")

Hulpmiddelen> Referenties> Microsoft Internet-besturingselementen
Bijbehorende DLL: ieframe.dll
Bron: Internet Explorer Browser

MSDN-InternetExplorer-object

Bestuurt een exemplaar van Windows Internet Explorer via automatisering.

Internet Explorer Objec Basic-leden

De onderstaande code zou moeten introduceren hoe het IE-object werkt en hoe het te manipuleren via VBA. Ik raad aan er doorheen te stappen, anders kan het fout raken tijdens meerdere navigaties.

Sub IEGetToKnow()
    Dim IE As InternetExplorer 'Reference to Microsoft Internet Controls
    Set IE = New InternetExplorer
    
    With IE
        .Visible = True 'Sets or gets a value that indicates whether the object is visible or hidden.
        
        'Navigation
        .Navigate2 "http://www.example.com" 'Navigates the browser to a location that might not be expressed as a URL, such as a PIDL for an entity in the Windows Shell namespace.
        Debug.Print .Busy 'Gets a value that indicates whether the object is engaged in a navigation or downloading operation.
        Debug.Print .ReadyState 'Gets the ready state of the object.
        .Navigate2 "http://www.example.com/2"
        .GoBack 'Navigates backward one item in the history list
        .GoForward 'Navigates forward one item in the history list.
        .GoHome 'Navigates to the current home or start page.
        .Stop 'Cancels a pending navigation or download, and stops dynamic page elements, such as background sounds and animations.
        .Refresh 'Reloads the file that is currently displayed in the object.
        
        Debug.Print .Silent 'Sets or gets a value that indicates whether the object can display dialog boxes.
        Debug.Print .Type 'Gets the user type name of the contained document object.
        
        Debug.Print .Top 'Sets or gets the coordinate of the top edge of the object.
        Debug.Print .Left 'Sets or gets the coordinate of the left edge of the object.
        Debug.Print .Height 'Sets or gets the height of the object.
        Debug.Print .Width 'Sets or gets the width of the object.
    End With
    
    IE.Quit 'close the application window
End Sub

Web schrapen

Het meest voorkomende wat u met IE doet, is wat informatie van een website schrapen, of een websiteformulier invullen en informatie verzenden. We zullen kijken hoe het te doen.

Laten we de broncode van example.com bekijken :

<!doctype html>
<html>
    <head>
        <title>Example Domain</title>
        <meta charset="utf-8" />
        <meta http-equiv="Content-type" content="text/html; charset=utf-8" />
        <meta name="viewport" content="width=device-width, initial-scale=1" />
        <style ... </style> 
    </head>

    <body>
        <div>
            <h1>Example Domain</h1>
            <p>This domain is established to be used for illustrative examples in documents. You may use this
            domain in examples without prior coordination or asking for permission.</p>
            <p><a href="http://www.iana.org/domains/example">More information...</a></p>
        </div>
    </body>
</html>

We kunnen de onderstaande code gebruiken om informatie te krijgen en in te stellen:

Sub IEWebScrape1()
    Dim IE As InternetExplorer 'Reference to Microsoft Internet Controls
    Set IE = New InternetExplorer
    
    With IE
        .Visible = True
        .Navigate2 "http://www.example.com"
        
        'we add a loop to be sure the website is loaded and ready.
        'Does not work consistently. Cannot be relied upon.
        Do While .Busy = True Or .ReadyState <> READYSTATE_COMPLETE 'Equivalent = .ReadyState <> 4
            ' DoEvents - worth considering. Know implications before you use it.
            Application.Wait (Now + TimeValue("00:00:01")) 'Wait 1 second, then check again.
        Loop
        
        'Print info in immediate window
        With .Document 'the source code HTML "below" the displayed page.
            Stop 'VBE Stop. Continue line by line to see what happens.
            Debug.Print .GetElementsByTagName("title")(0).innerHtml 'prints "Example Domain"
            Debug.Print .GetElementsByTagName("h1")(0).innerHtml 'prints "Example Domain"
            Debug.Print .GetElementsByTagName("p")(0).innerHtml 'prints "This domain is established..."
            Debug.Print .GetElementsByTagName("p")(1).innerHtml 'prints "<a href="http://www.iana.org/domains/example">More information...</a>"
            Debug.Print .GetElementsByTagName("p")(1).innerText 'prints "More information..."
            Debug.Print .GetElementsByTagName("a")(0).innerText 'prints "More information..."
            
            'We can change the localy displayed website. Don't worry about breaking the site.
            .GetElementsByTagName("title")(0).innerHtml = "Psst, scraping..."
            .GetElementsByTagName("h1")(0).innerHtml = "Let me try something fishy." 'You have just changed the local HTML of the site.
            .GetElementsByTagName("p")(0).innerHtml = "Lorem ipsum........... The End"
            .GetElementsByTagName("a")(0).innerText = "iana.org"
        End With '.document
        
        .Quit 'close the application window
    End With 'ie
    
End Sub

Wat is er aan de hand? De belangrijkste speler hier is het .Document , dat is de HTML-broncode. We kunnen enkele zoekopdrachten toepassen om de gewenste collecties of objecten te krijgen.
Bijvoorbeeld de IE.Document.GetElementsByTagName("title")(0).innerHtml . GetElementsByTagName retourneert een verzameling HTML-elementen met de tag ' title '. Er is slechts één zo'n tag in de broncode. De collectie is gebaseerd op 0. Dus om het eerste element te krijgen voegen we (0) . In ons geval willen we nu alleen de innerHtml (een String), niet het Element-object zelf. Dus specificeren we de eigenschap die we willen.

Klik

Om een link op een site te volgen, kunnen we meerdere methoden gebruiken:

Sub IEGoToPlaces()
    Dim IE As InternetExplorer 'Reference to Microsoft Internet Controls
    Set IE = New InternetExplorer
    
    With IE
        .Visible = True
        .Navigate2 "http://www.example.com"
        Stop 'VBE Stop. Continue line by line to see what happens.
        
        'Click
        .Document.GetElementsByTagName("a")(0).Click
        Stop 'VBE Stop.
        
        'Return Back
        .GoBack
        Stop 'VBE Stop.
        
        'Navigate using the href attribute in the <a> tag, or "link"
        .Navigate2 .Document.GetElementsByTagName("a")(0).href
        Stop 'VBE Stop.
        
        .Quit 'close the application window
    End With
End Sub

Microsoft HTML Object Library of IE Beste vriend

Om het maximale uit de HTML te halen die in IE wordt geladen, kunt (of zou moeten) een andere bibliotheek gebruiken, namelijk Microsoft HTML-objectbibliotheek . Hierover meer in een ander voorbeeld.

IE Belangrijkste problemen

Het belangrijkste probleem met IE is controleren of de pagina klaar is met laden en klaar is om ermee te werken. De Do While... Loop helpt, maar is niet betrouwbaar.

Ook is het gebruik van IE om HTML-inhoud te schrapen OVERKILL. Waarom? Omdat de browser bedoeld is om te browsen, dwz de webpagina met alle CSS, JavaScripts, afbeeldingen, pop-ups, enz. Weer te geven. Als u alleen de onbewerkte gegevens nodig hebt, overweeg dan een andere aanpak. Bijvoorbeeld met behulp van XML HTTPRequest . Hierover meer in een ander voorbeeld.



Modified text is an extract of the original Stack Overflow Documentation
Licentie onder CC BY-SA 3.0
Niet aangesloten bij Stack Overflow