How Do I Automatically Update the ChromeDriver or EdgeDriver in VBA?
Asked Answered
L

6

6

I have searched the web for a solution to "auto-update" my Selenium EdgeDriver automatically. For those who use SeleniumBasic, you know it can be a hassle to manually download the driver from the respective webpage every so often when your main Host browser gets a major update.

In my web searching, I have found support for other languages to "auto-update" their versions of these drivers, but VBA, as usual, was lacking support.

Now I don't claim this to be the perfect solution, but it at least works. The problem I can see in the future is that layouts of each respective webpage may change, so I do welcome updates if this is the case and I will try to update as well. But for the most part, it should just work.

While this is a Self-Answered question, I absolutely would love to see other methods posted here for myself and other users to try out. SeleniumBasic is a good tool for certain applications, but often lacks community support as VBA is not as widely used in the community as other languages - at least not on a more sophisticated level.

Late answered 16/6, 2021 at 4:0 Comment(1)
For those out there who are not familiar with SeleniumBasic, you can download it from florentbr's Github here. It hasn't been updated since 2016, but it still works quite well. This will allow web browser automation within MS Office.Calder
L
5

I should start out by saying that I am only supporting Chrome and Edge drivers for the time being. But if you can follow along, you might be able to add your own support for any of the other SeleniumBasic-supported WebDrivers.

Before we get started, it is important to enable the following References by going to Tools > References within the VBE: enter image description here

Next, you need to create a Class Module named SeleniumWebDriver.
enter image description here

I decided to make this a Class Object because I intend to build a little on it in the future. You may add your own Properties and functions as you wish, but the code being provided will only allow updating the WebDrivers, at least for now.

Here is the complete Class Module Code:

Option Explicit

Rem Did Chrome change their file url and break your code?
' Check for an update: https://mcmap.net/q/1673878/-how-do-i-automatically-update-the-chromedriver-or-edgedriver-in-vba

Private ChromeDriver As Selenium.ChromeDriver
Private EdgeDriver As Selenium.EdgeDriver
Private SeleniumFolder As String
Private TempZipFile As String
Private ChromeInit As Boolean, EdgeInit As Boolean

Public Enum dType
    Chrome
    Edge
End Enum

Public Property Get SeleniumFolderPath() As String
    SeleniumFolderPath = SeleniumFolder
End Property

Public Property Let SeleniumFolderPath(ByVal FolderPath As String)
    SeleniumFolder = FolderPath
End Property
    
Public Sub UpdateDriver(ByVal DriverType As dType)

    'URLs to the drivers' home pages to which we can grab the curr versions
    Dim URLPath As String
    Select Case DriverType
    Case dType.Chrome
        URLPath = "https://chromedriver.chromium.org/home"
    Case dType.Edge
        URLPath = "https://developer.microsoft.com/en-us/microsoft-edge/tools/webdriver/"
    End Select
    
    'Grab the current Version # from the driver's webpage
    Dim Doc As New HTMLDocument, DriverVer As String
    With New MSXML2.XMLHTTP60
        .Open "GET", URLPath
        .send
        Doc.body.innerHTML = .responseText
    End With
    DriverVer = getCurrentVersion(Doc, DriverType)
    
    DownloadUpdatedDriver DriverVer, DriverType
    ExtractZipAndCopy DriverType

End Sub

' For use in a later project. Not needed at this time
Private Sub InitializeDriver(ByVal DriverType As dType)
    Select Case DriverType
    Case dType.Chrome
        Set ChromeDriver = New Selenium.ChromeDriver
        ChromeDriver.Start
        ChromeInit = True
    Case dType.Edge
        Set EdgeDriver = New Selenium.EdgeDriver
        EdgeDriver.Start
        EdgeInit = True
    End Select
End Sub

Private Function getCurrentVersion(Doc As HTMLDocument, DriverType As dType) As String

    Dim div As HTMLDivElement

    Select Case DriverType
    Case dType.Chrome
        For Each div In Doc.getElementsByTagName("p")
            If div.innerText Like "Latest stable release*" Then
                With New VBScript_RegExp_55.RegExp
                    .Pattern = "ChromeDriver\s([\d\.]+)\b"
                    getCurrentVersion = .Execute(div.innerText)(0).SubMatches(0)
                    Exit Function
                End With
            End If
        Next
    Case dType.Edge
        With New VBScript_RegExp_55.RegExp
            .Pattern = "Version:\s([\d\.]+)"
            For Each div In Doc.getElementsByClassName("module")(0).getElementsByTagName("p")
                If .test(div.innerText) Then
                    getCurrentVersion = .Execute(div.innerText)(0).SubMatches(0)
                    Exit Function
                End If
            Next
        End With
    End Select

End Function

Private Sub DownloadUpdatedDriver(ByVal CurrVersion As String, DriverType As dType)
    
    Dim URLPath As String
    Select Case DriverType
    Case dType.Chrome
        URLPath = "https://chromedriver.storage.googleapis.com/" & CurrVersion & "/chromedriver_win32.zip"
    Case dType.Edge
        Kill Environ$("LocalAppData") & "\SeleniumBasic\Driver_Notes\*.*"
        URLPath = "https://msedgedriver.azureedge.net/" & CurrVersion & "/edgedriver_win64.zip"
    End Select
    
    Dim FileStream As New ADODB.Stream
    With New MSXML2.XMLHTTP60
        .Open "GET", URLPath
        .send
        FileStream.Open
        FileStream.Type = adTypeBinary
        FileStream.Write .responseBody
        FileStream.SaveToFile TempZipFile, adSaveCreateOverWrite
        FileStream.Close
    End With
    
End Sub

Private Sub ExtractZipAndCopy(ByVal DriverType As dType)

    Dim FileName As String
    Select Case DriverType
    Case dType.Chrome: FileName = "\chromedriver.exe"
    Case dType.Edge: FileName = "\edgedriver.exe"
    End Select

    'Delete the old WebDriver
    Kill SeleniumFolder & FileName
    
    'Copy the new driver from .zip file to SeleniumBasic folder
    Dim oShell As New shell
    oShell.Namespace(SeleniumFolder).CopyHere oShell.Namespace(TempZipFile).Items
    
    'Selenium VBA expects 'edgedriver' for edge, but new drivers are named 'msedgedriver'.
    'If we are updating Edge, we need to rename the file
    If DriverType = dType.Edge Then
        Name SeleniumFolder & "msedgedriver.exe" As SeleniumFolder & "edgedriver.exe"
    End If
        
    'Delete the temporary zip file
    Kill TempZipFile

End Sub

Private Sub Class_Initialize()

    ' Set the default file path. Can be modified later using ChromeDriverPath property
    SeleniumFolder = Environ$("LocalAppData") & "\SeleniumBasic\"
    TempZipFile = Environ$("LocalAppData") & "\Temp\WebDriver.zip"

End Sub

Now that you've created your Selenium Class, you can now use it in a standard module such as: enter image description here

Important Tip: I am not sure if there is a delay between when you update your web browser and when the drivers are officially released. Therefore before updating your driver, I would put some error handling to see if Selenium throws an error first. If the driver does not match the browser version, Selenium will throw error # 33. If you check for this error, you should be safe to go ahead and update the WebDriver at this point. What we want to prevent is that you update your driver before your browser is automatically updated, causing mismatching versions.

It is also possible that your browser may update and the Selenium driver hasn't been released yet - but unfortunately that is not something that we can control.


The remainder of this answer will just go into some detail as to what it's doing. If you don't care, you may leave now.

First, as with any other object, we have to initialize it. In the above example, we do that with the With New SeleniumWebDriver statement. This fires the Class_Initialize() event here:

Private Sub Class_Initialize()

    ' Set the default file path. Can be modified later using ChromeDriverPath property
    SeleniumFolder = Environ$("LocalAppData") & "\SeleniumBasic\"
    TempZipFile = Environ$("LocalAppData") & "\Temp\WebDriver.zip"

End Sub

The purpose of this is to set the default file paths for the SeleniumBasic folder and temp file. However, if your folder is somewhere else, this class has a property to which you can change the folder manually. Just use the ClassObj.SeleniumFolderPath() property to establish your new path.

The TempZipFile is a class-scoped variable that will store the .zip file you download from the respective websites.

Upon calling the UpdateDriver method, the class will place a GET request to the respective driver's webpage, then grab the current version # from the page. It will then pass this driver version to the DownloadUpdatedDriver routine, which stores the download links for each respective driver. For Chrome, the link is: https://chromedriver.storage.googleapis.com/<Version#>/chromedriver_win32.zip, and for Edge it's: https://msedgedriver.azureedge.net/<Version#>/edgedriver_win64.zip. It's important to realize that if you happen to be using the 32 bit version of Edge, you will need to change the URL to edgedriver_win32.zip. This routine downloads the .zip file to your local AppData's Temp Folder.

After the file has been downloaded, we then proceed to call the ExtractZipAndCopy routine. This simply extracts the .exe files to the Selenium Folder, first deleting the old file. Edge does a little extra maintenance work, but you're now essentially updated!

I hope this helps someone out there who is annoyed as I am having to periodically update these drivers and was wanting an automated solution. Please feel free to edit this answer if minor changes are needing to be made, such as if a URL is broken.

Late answered 16/6, 2021 at 4:0 Comment(3)
It looks like you don't do a check on browser which means you can end up, certainly in the case of auto-updates, with a beta chrome browser but a stable release chromedriver. I do see your warning note. You could always determine the installed browser version. I get why you are checking the innerText for stable release. It is more robust then just using querySelector though, if html is stable then loop could be removed and just apply regex to doc.querySelector("li > [dir] a").innerText.Salute
I need to re-read the rest when laptop isn't so hot might explode .Add in the ByVals for getCurrentVersion What would initiate this? Would you have windows scheduler run a daily check with a script to pick up browser version then retrieve the appropriate driver if available? Thanks for sharing +Salute
I'm sure there are easier ways but I know this works https://www.ozgrid.com/forum/index.php?thread/72260-get-version-of-dll-file/ for chrome browser version. I substitute in Filename = "chrome.exe" and Directory = "C:\Program Files (x86)\Google\Chrome\Application\" This will also work for determining current chomedriver. In the return you can compare Product version:Salute
G
2

There is now an API to check Latest Release of ChromeDriver. So the code can become shorter. Also, adding a functionality to run the update only if the current chrome version does not match installed chromedriver version. And to copy using administrator rights. I am not using Edge so that code functionality is not there in my code.

Function chkchromever()
Tempfolder = "D:\"
TempZipFile = Tempfolder & "Chromedriver.zip"
SeleniumFolder = Environ$("ProgramW6432") & "\SeleniumBasic\"
TempDrvFile = Tempfolder & "Chromedriver.exe"
'Delete chromedriver.exe from temporary folder if it already exists
If Dir(TempDrvFile) <> "" Then
    Kill (TempDrvFile)
End If


Dim oShell  As New WshShell
Dim objHttp As Object
Set objHttp = CreateObject("MSXML2.ServerXMLHTTP.6.0")

'Get chrome version
chrversion = CreateObject("WScript.Shell").RegRead("HKEY_CURRENT_USER\Software\Google\Chrome\BLBeacon\version")
dotsarr = Split(chrversion, ".")
leftchrver = dotsarr(0) & dotsarr(1)

'Get chromedriver version
gspath = Chr(34) & SeleniumFolder & "chromedriver.exe" & Chr(34)
torun = gspath & " --version"
errcode = oShell.Exec(torun).StdOut.ReadAll
verarr = Split(errcode, " ")
chrdrv = verarr(1)
dotsarr2 = Split(chrdrv, ".")
leftchrdrv = dotsarr(0) & dotsarr(1)

'If major version mismatch (first two numbers) then ask if update required
If leftchrver <> leftchrdrv Then
    myyn = MsgBox("Wrong version of chromedriver. " & vbCrLf & "Chrome version is " & chrversion & vbCrLf & "Chrome driver version is " & chrdrv, vbYesNo, "Do you want to update Chromedriver ?")
    If myyn = vbNo Then Exit Function
    'Get latest release version of chromedriver which matches installed version of Chrome
    url = "https://chromedriver.storage.googleapis.com/LATEST_RELEASE_" & dotsarr(0)
    Call objHttp.Open("GET", url, False)
    Call objHttp.send("")
    version_number = objHttp.responseText
    dotsarr3 = Split(version_number, ".")
    leftversion_no = dotsarr3(0) & dotsarr3(1)
    If leftchrver = leftversion_no Then
        'If chromedriver found then download it
        download_url = "https://chromedriver.storage.googleapis.com/" + version_number + "/chromedriver_win32.zip"
        Call objHttp.Open("GET", download_url, False)
        Call objHttp.send("")
        Set fileStream = New ADODB.Stream
        With fileStream
            .Open
            .Type = adTypeBinary
            .Write objHttp.responseBody
            .Position = 0
            .SaveToFile TempZipFile, adSaveCreateOverWrite
            .Close
        End With
        'Copy the new driver from .zip file to SeleniumBasic folder
        Set oApp = CreateObject("Shell.Application")
        oApp.Namespace(Tempfolder).CopyHere oApp.Namespace(TempZipFile).Items
        
        'Create batch file to copy chromedriver.exe to Seleniumbasic folder and run it using Administrator rights
        tmpbatpath = Tempfolder & "copychdrv.bat"
        'Check if Chromedriver downloaded successfully
        If Dir(TempDrvFile) <> "" Then
            Open tmpbatpath For Output As #1
            'Enable these if required to copy chromedriver.exe
            '        Print #1, "taskkill /f /im  GoogleCrashHandler.exe"
            '        Print #1, "taskkill /f /im  GoogleCrashHandler64.exe"
            '        Print #1, "taskkill /f /im  Chrome.exe"
            '        Print #1, "taskkill /f /im  Googleupdate.exe"
            If IsProcessRunning("Chromedriver.exe") Then
                Print #1, "taskkill /f /im  Chromedriver.exe"
            End If
            Print #1, "copy " & Chr(34) & TempDrvFile & Chr(34) & " " & Chr(34) & SeleniumFolder & "Chromedriver.exe" & Chr(34) & "/y"
            Close #1
            'copy it now by running batch file
            success = ShellExecute(0, "runas", tmpbatpath, aPic, vbNullString, SW_SHOWNORMAL)
        End If
        'Cleanup
        If Dir(TempZipFile) <> "" Then
            Kill (TempZipFile)
        End If
        If Dir(tmpbatpath) <> "" Then
            Kill (tmpbatpath)
        End If
    End If
End If
End Function
Gyatt answered 27/7, 2021 at 13:44 Comment(0)
C
1

As i am on a company PC, I updated the code to work on a locked PC

    Option Explicit
'**********************************************************
' PUBLIC FUNCTION
'/
'**********************************************************
' @Fn       chkchromever
'
' @brief    Check if Selenium Crome Driver is up to date or update it
'
' @param    checks Crome version and Installed and availible Driver for Selenium
'
' @SUBs     IsProcessRunning, ShellExecute
'
' Librarys  Selenium Type library
'           Windows Script Host Object Model            - Dim oShell  As New WshShell ,
'           Microsoft ActiveX Data Objects 6.1 Library  - Set fileStream = New ADODB.Stream
'
' @return   new driver
'/

Public Declare Function ShellExecute _
    Lib "shell32.dll" _
        Alias "ShellExecuteA" ( _
            ByVal Hwnd As Long, _
            ByVal lpOperation As String, _
            ByVal lpFile As String, _
            ByVal lpParameters As String, _
            ByVal lpDirectory As String, _
            ByVal nShowCmd As Long) _
As Long

Function chkchromever()
Dim tempfolder As Variant, TempZipFile As Variant
Dim SeleniumFolder As String, TempDrvFile As String
Dim chrversion As String, leftchrver As String
Dim dotsarr() As String
Dim gspath As String, torun As String, errcode As String
Dim verarr() As String, chrdrv As String, leftchrdrv As String
Dim dotsarr2() As String
Dim myyn As Integer
Dim Url As String, version_number As String, leftversion_no As String
Dim dotsarr3() As String
Dim download_url As String

tempfolder = "C:\Temp\"
TempZipFile = tempfolder & "Chromedriver.zip"
'SeleniumFolder = Environ$("ProgramW6432") & "\SeleniumBasic\"
SeleniumFolder = Environ$("LOCALAPPDATA") & "\SeleniumBasic\"
TempDrvFile = tempfolder & "Chromedriver.exe"
'Delete chromedriver.exe from temporary folder if it already exists
If Dir(TempDrvFile) <> "" Then
    Kill (TempDrvFile)
End If

Dim oShell  As New WshShell
Dim objHttp As Object
Set objHttp = CreateObject("MSXML2.ServerXMLHTTP.6.0")

'Get chrome version
chrversion = CreateObject("WScript.Shell").RegRead("HKEY_CURRENT_USER\Software\Google\Chrome\BLBeacon\version")
dotsarr = Split(chrversion, ".")
leftchrver = dotsarr(0) & dotsarr(1)

'Get chromedriver version
gspath = Chr(34) & SeleniumFolder & "chromedriver.exe" & Chr(34) ' chr34 er gåseøjne
torun = gspath & " --version"
errcode = oShell.Exec(torun).StdOut.ReadAll
verarr = Split(errcode, " ")
chrdrv = verarr(1)
dotsarr2 = Split(chrdrv, ".")
leftchrdrv = dotsarr2(0) & dotsarr2(1)

'If major version mismatch (first two numbers) then ask if update required
If leftchrver <> leftchrdrv Then
    myyn = MsgBox("Wrong version of chromedriver. " & vbCrLf & "Chrome version is " & chrversion & vbCrLf & "Chrome driver version is " & chrdrv, vbYesNo, "Do you want to update Chromedriver ?")
    If myyn = vbNo Then Exit Function
    'Get latest release version of chromedriver which matches installed version of Chrome
    Url = "https://chromedriver.storage.googleapis.com/LATEST_RELEASE_" & dotsarr(0)
    Call objHttp.Open("GET", Url, False)
    Call objHttp.send("")
    version_number = objHttp.responseText
    dotsarr3 = Split(version_number, ".")
    leftversion_no = dotsarr3(0) & dotsarr3(1)
    If leftchrver = leftversion_no Then
        'If chromedriver found then download it
        download_url = "https://chromedriver.storage.googleapis.com/" + version_number + "/chromedriver_win32.zip"
        Call objHttp.Open("GET", download_url, False)
        Call objHttp.send("")
        Dim fileStream As Object
        Set fileStream = New ADODB.Stream
        With fileStream
            .Open
            .Type = adTypeBinary
            .Write objHttp.responseBody
            .Position = 0
            .SaveToFile TempZipFile, adSaveCreateOverWrite
            .Close
        End With
        'unzip file
        Dim oApp As Object
        Set oApp = CreateObject("Shell.Application")
        oApp.Namespace(tempfolder).CopyHere oApp.Namespace(TempZipFile).Items
        'Check if Chromedriver downloaded successfully
        If Dir(TempDrvFile) <> "" Then
            If IsProcessRunning("Chromedriver.exe") Then
               Shell "cmd /c""" & "taskkill /f /im  Chromedriver.exe"
            End If
            'Copy / Overwrite file in SeleniumBasic folder
            FileCopy TempDrvFile, SeleniumFolder & "Chromedriver.exe"
        End If
        'Cleanup
        If Dir(TempZipFile) <> "" Then
            Kill (TempZipFile)
        End If
        If Dir(TempDrvFile) <> "" Then
            Kill (TempDrvFile)
        End If
    End If
End If
End Function

Function IsProcessRunning(process As String)
    Dim objList As Object
    
    Set objList = GetObject("winmgmts:") _
        .ExecQuery("select * from win32_process where name='" & process & "'")
    
    IsProcessRunning = objList.Count > 0
End Function
Chita answered 9/5, 2022 at 12:51 Comment(2)
Your answer could be improved with additional supporting information. Please edit to add further details, such as citations or documentation, so that others can confirm that your answer is correct. You can find more information on how to write good answers in the help center.Preserve
After O365 update i cant update driver, i get error 70 at this line errcode = oShell.Exec(torun).StdOut.ReadAllChita
O
1

I had to modify the code posted above by Jesper Martin Schumacher as our IT department has updated all Office Applications to 64-bit.

That code was failing on instances of "New" keyword, so I researched and found:

compile error User-defined type not defined at "oShell As WshShell"

The suggestion there was to use "Late Binding" CreateObject method instead, as below.

Set oShell = CreateObject("WScript.Shell") 'Had to edit this line. It WAS "Set oShell = New WshShell"

Set fileStream = CreateObject("ADODB.Stream") 'Had to edit this line. It WAS "Set fileStream = New ADODB.Stream"
Olwena answered 8/1, 2023 at 22:36 Comment(0)
H
1
Private bot As New WebDriver

Public sub another()
On Error Resume Next

 Bot.Start "chrome"

 If Err = 33 Then Call ch_update

 Bot.Start "chrome"

On Error GoTo -1
 End Sub

 Public Sub ch_update()
    With New SeleniumWebDriver
 .chkchromever

End With

End Sub

  Option Explicit
'**********************************************************
' PUBLIC FUNCTION

 Private Declare PtrSafe Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
    (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long



Function chkchromever()
Dim tempfolder As Variant, TempZipFile As Variant
Dim SeleniumFolder As String, TempDrvFile As String
Dim chrversion As String, leftchrver As String
Dim dotsarr() As String
Dim gspath As String, torun As String, errcode As String
Dim verarr() As String, chrdrv As String, leftchrdrv As String
Dim dotsarr2() As String
Dim myyn As Integer
Dim Url As String, version_number As String, leftversion_no As String
Dim dotsarr3() As String
Dim download_url As String

tempfolder = Environ$("LocalAppData") & "\Temp\"
TempZipFile = tempfolder & "Chromedriver.zip"

SeleniumFolder = "C:\Program Files" & "\SeleniumBasic\"

   If Dir(SeleniumFolder) <> "" Then

  Else

     SeleniumFolder = Environ$("LOCALAPPDATA") & "\SeleniumBasic\"

 End If
Herb answered 20/7, 2023 at 1:56 Comment(1)
As it’s currently written, your answer is unclear. Please edit to add additional details that will help others understand how this addresses the question asked. You can find more information on how to write good answers in the help center.Preserve
P
0

Here is a script to download the latest Edge Driver to a file share (\\pw30\download\Selenium) and archive old file.

Set fso = CreateObject("Scripting.FileSystemObject")
Set oShell = WScript.CreateObject("WSCript.shell")
set oShellApp = CreateObject("Shell.Application")
Set oHttp = CreateObject("MSXML2.ServerXMLHTTP.6.0") 
oHttp.Open "GET", "https://developer.microsoft.com/en-us/microsoft-edge/tools/webdriver", False
oHttp.Send
s = oHttp.responseText
iPos = InStr(1, s,"Stable Channel")
iPos = InStr(iPos, s,"/edgedriver_win64.zip""")
s = Mid(s, iPos - 50, 100)
iPos = InStr(1, lcase(s),"https://")
s = Mid(s, iPos)
iPos = InStr(1, s, """")
sUrl = Mid(s, 1, iPos - 1)

sFolder = GetBaseFolder()
sFilePath = sFolder & "\edgedriver_win64.zip"

If fso.FileExists(sFilePath) Then
  fso.DeleteFile sFilePath, True
End If

DownloadFile sUrl, sFilePath
MsgBox "Downloaded " & sFilePath

sEdgeDriverPath = sFolder & "\msedgedriver.exe"
If fso.FileExists(sEdgeDriverPath) Then
  fso.DeleteFile sEdgeDriverPath, True
End If

oShellApp.Namespace(sFolder & "\").CopyHere oShellApp.Namespace(sFilePath).Items
If fso.FileExists(sEdgeDriverPath) = False Then
  MsgBox "File could not be unzipped"
  WScript.Quit
End If

sSeleniumVersion = GetMajorVersion(fso.GetFileVersion(sEdgeDriverPath))
MsgBox "Downloaded Version: " & sSeleniumVersion

sDestFilePath = "\\pw30\download\Selenium\edgedriver.exe"
sDestSeleniumVersion = GetMajorVersion(fso.GetFileVersion(sDestFilePath))

If sDestSeleniumVersion = sSeleniumVersion Then
  MsgBox "No Action Needed. Quitting. Versions are is the same " & sSeleniumVersion & vbCrLf & sEdgeDriverPath & vbCrLf & sDestFilePath 
  WScript.Quit
Else
  If fso.FileExists(sDestFilePath) Then
    fso.DeleteFile sDestFilePath, True
    fso.CopyFile sEdgeDriverPath, sDestFilePath
    MsgBox "Downloaded Version: " & sSeleniumVersion & " <> Dest Version " & sDestSeleniumVersion & " Updated: " & sDestFilePath 
  End If
End If

sDestFilePath = "\\pw30\download\Selenium\edgedriver_" & sSeleniumVersion & ".exe"
If fso.FileExists(sDestFilePath) = False Then
  fso.CopyFile sEdgeDriverPath, sDestFilePath
  MsgBox " Updated: " & sDestFilePath 
End If

MsgBox "Done"

'==========================================
Sub DownloadFile(sUrl, sFilePath)
  Dim oHTTP: Set oHTTP = CreateObject("Microsoft.XMLHTTP")
  oHTTP.Open "GET", sUrl, False
  oHTTP.Send

  If oHTTP.Status = 200 Then 
    Set oStream = CreateObject("ADODB.Stream") 
    oStream.Open 
    oStream.Type = 1 
    oStream.Write oHTTP.ResponseBody 
    oStream.SaveToFile sFilePath, 2 
    oStream.Close 
  Else
    MsgBox "Error Status: " & oHTTP.Status & ", URL:" & sUrl
  End If
End Sub

Function GetBaseFolder()
  Set oFile = fso.GetFile(WScript.ScriptFullName)
  GetBaseFolder = oFile.ParentFolder
End Function

Function GetMajorVersion(s)
  i = InStr(s,".")
  If i <> 0 Then
    GetMajorVersion = Mid(s, 1,i - 1)
  Else
    GetMajorVersion = s
  End If
End Function

Here is script that will use the downloaded file if needed.

Dim oShell: Set oShell = CreateObject("WScript.Shell")
Dim sEdgeVersion, sSeleniumVersion 
Dim sEdgeDriverPath: sEdgeDriverPath = GetEdgeDriverPath()
If fso.FileExists(sEdgeDriverPath) Then
    sSeleniumVersion = GetMajorVersion(fso.GetFileVersion(sEdgeDriverPath))
    sEdgeVersion = GetMajorVersion(oShell.RegRead("HKEY_CURRENT_USER\Software\Microsoft\Edge\BLBeacon\version") & "")
    If sEdgeVersion <> sSeleniumVersion Then
        sServerSeleniumFilePath = "\\pw30\download\Selenium\EdgeDriver.exe"
        sServerSeleniumVersion = GetMajorVersion(fso.GetFileVersion(sServerSeleniumFilePath))
        If sServerSeleniumVersion = sSeleniumVersion Then
            TryToUpdateSelenium            
        Else
            UpdateSeleniumVer sSeleniumVersion
        End If
    End If
End If

Sub UpdateSeleniumVer(sSeleniumVersion)
    Dim sFromFilePath: sFromFilePath = "\\pw30\download\Selenium\EdgeDriver_" & sSeleniumVersion & ".exe"

    If fso.FileExists(sFromFilePath) = False Then    
        Exit Sub
    End If

    On Error Resume Next

    If Err.Number <> 0 Then
        Err.Clear
    End If

    Dim sToFilePath: sToFilePath = GetEdgeDriverPath()
    If fso.FileExists(sToFilePath) Then    
        fso.DeleteFile sToFilePath, True
    End If
    
    fso.CopyFile sFromFilePath, sToFilePath
    If Err.Number <> 0 Then
        WScript.Echo "Could not copy: " & sFromFilePath & " to: " & sToFilePath & " Error: " & Err.Description

        oShell.Run "explorer.exe /e," & fso.GetFile(sFromFilePath).ParentFolder.Path
        oShell.Run "explorer.exe /e," & oFile.ParentFolder.Path
    End If
End Sub

Function TryToUpdateSelenium()
    On Error Resume Next

    If Err.Number <> 0 Then
        Err.Clear
    End If

    Dim sToFilePath: sToFilePath = GetEdgeDriverPath()

    Dim sFromFilePath: sFromFilePath = "\\pw30\download\Selenium\EdgeDriver.exe"
    If fso.FileExists(sFromFilePath) = False Then
        WScript.Echo "Could not find: " & sFromFilePath
        TryToUpdateSelenium = False
        Exit Function
    End If

    If fso.FileExists(sToFilePath) Then
        fso.DeleteFile sToFilePath, True
    End If

    fso.CopyFile sFromFilePath, sToFilePath

    If Err.Number <> 0 Then
        WScript.Echo "Could not copy: " & sFromFilePath & " to: " & sToFilePath & " Error: " & Err.Description

        oShell.Run "explorer.exe /e," & fso.GetFile(sFromFilePath).ParentFolder.Path
        oShell.Run "explorer.exe /e," & oFile.ParentFolder.Path
    End If

    TryToUpdateSelenium = Err.Number = 0
End Function

Function GetMajorVersion(s)
  i = InStr(s,".")
  If i <> 0 Then
    GetMajorVersion = Mid(s, 1,i - 1)
  Else
    GetMajorVersion = s
  End If
End Function

Function GetEdgeDriverPath()
    Dim sSeleniumFilePath: sSeleniumFilePath = oShell.RegRead("HKEY_CLASSES_ROOT\CLSID\{0277FC34-FD1B-4616-BB19-0809389E78C4}\InprocServer32\CodeBase") 'C:\Users\80014379\AppData\Local\SeleniumBasic\Selenium.dll
    Dim oFile: Set oFile = fso.GetFile(sSeleniumFilePath)
    GetEdgeDriverPath = oFile.ParentFolder.Path & "\EdgeDriver.exe"
End Function
Picked answered 1/2 at 22:29 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.