Installing


RunThis.cmd

IF EXIST "C:\Program Files (x86)\Microsoft Office\Office16\Library" ( 
   reg add "HKEY_CURRENT_USER\Software\Microsoft\Office\16.0\Excel\Options"
       /v "AltStartup" /d "Y:\SharedDrive\myFolder\xlStart" /f

   copy /Y Y:\SharedDrive\myFolder\*.* "C:\Program Files (x86)\Microsoft Office\Office16\library\"

   cscript "C:\Program Files (x86)\better solutions\excel_addin.vbs"
      /a "c:\Program Files (x86)\microsoft office\Office16\library\exceladdin1.xla"

   cscript "C:\Program Files (x86)\better solutions\excel_addin.vbs"
      /l "c:\Program Files (x86)\microsoft office\Office16\library\exceladdin1.xla"

   EXIT /B
)

excel_addin.vbs

This is a VBScript Source File
The script will accept parameters /a, /r /l, and the file name to automate the excel add-in add and removal
Syntax: cscript excel_addin.vbs /a|/r|/l filename

Dim filename 
Dim objfs

Set objfs = CreateObject("Scripting.FileSystemObject")

If wscript.arguments.length <> 2 Then
    Wscript.Echo "Syntax: cscript excel-addin.vbs /a|/r filename" &_
                    vbLf & " /a for adding an excel addin" &_
                    vbLf & " /l for loading an excel addin" &_
                    vbLf & " /r for removing an excel addin" &_
                    vbLf & "eg: cscript excel_addin.vbs /a c:\temp\finesse.xll" &_
                    vbLf & "eg: cscript excel_addin.vbs /l c:\temp\finesse.xll" &_
                    vbLf & "eg: cscript excel_addin.vbs /r c:\temp\finesse.xll"
    Wscript.Quit -1
End If

operation = wscript.arguments.item(0)
filename = wscript.arguments.item(1)

If objfs.fileexists(filename) Then
  If UCase(operation) = "/A" Then

                Set oXL = CreateObject("Excel.Application")
                oXL.Workbooks.Add
                Set oAddin = oXL.AddIns.Add(filename, True)
                oAddin.Installed = True
                oXL.Quit
                Set oXL = Nothing

  Elseif UCase(operation) = "/L" Then

                Set oXL = CreateObject("Excel.Application")
                oXL.Workbooks.Add
                Set oAddin = oXL.AddIns.Add(filename, True)
                oXL.Quit
                Set oXL = Nothing

  ElseIf UCase(operation) ="/R" Then

                Set oXL = CreateObject("Excel.Application")
                oXL.Workbooks.Add
                Set oAddins = oXL.AddIns.Add(filename, True)
                oAddIns.Installed = False
                oXL.Quit
                Set oXL = Nothing

  Else
     wscript.echo "Operation not recognized, please use /a for add, /r for removal, /l for load"
  End If
Else
     wscript.echo Filename & " does not exist, please check the file path"
End If

set OXL = Nothing

Dim oWsh
Dim lres

Set oWsh = CreateObject("wscript.shell")
On Error Resume Next

If (Ucase(operation) = "/A") Then
   lres = owsh.Run("cscript //nologo S:\Logon\ResetAddinKeeperFile.vbs
             /Addin:""" & filename & """ /Action:Add", 0, True)
   If lres <> 0 Then
     WScript.Quit lres
   End If

ElseIf (Ucase(operation) = "/R") then
   lres = oWsh.Run("cscript //nologo S:\Logon\ResetAddinKeeperFile.vbs
             /Addin:""" & filename & """ /Action:Remove", 0, True)
   If lres <> 0 Then
      WScript.Quit lres
   End If
End If

Set oWsh = Nothing

© 2025 Better Solutions Limited. All Rights Reserved. © 2025 Better Solutions Limited TopPrevNext