Programmatically set DLL search path in VBA macro - vba

The problem
I have a word template which uses VBA's Declare statement to link to a dll, whose path can be determined within the VBA macro
I want to delploy this to the users %APPDATA%\Microsoft\Word\STARTUP directory
I DON'T want to permanently change the user's PATH environment variable (temporarily would be OK, but this doesn't seem to work as they don't get refreshed until application restart)
Attempted solution
I tried dynamically adding the code with the Declare statements using ThisDocument.VBProject.CodeModule.AddFromString(code) which works when loading the template from a normal directory, but when the template is within Word\STARTUP, it gives the following error:
Run-time error '50289':
Can't perform operation since the
project is protected.
And setting the registry key "HKEY___LOCAL_MACHINE\Software\Microsoft\Office\11.0\Word\Security\AccessVBOM" to 1 doesn't fix this when the template is in Word\STARTUP
I'm really struggling to find a solution. If anyone knows a way to do this, that would be great.

Frankly, I don't know what's the problem with using all those VBA code injection, assembly generation for LoadLibrary() calls, etc techniques that I've seen used for this simple task. In my project I use simple code to load dll from the same location as the workbook, like this:
Declare Function MyFunc Lib "MyDll.dll" (....) As ...
Sub Test()
....
ChDir ActiveWorkbook.Path
... = MyFunc(....)
End Sub
Excel 2003 at least, has no problem loading the dll from the current path, Set ChDir to whatever path your DLL has. You might also need to change your current drive which is separate from current path. You have to do it only once, before the first function call, after it the DLL stays attached no matter where your current path is, so you may do it once in workbook_open and not bother about the path later. I provide an empty dummy function in the DLL just for this pupose. I don't think MS Word is any different on this.
Private Declare Sub Dummy Lib "MyDLL.dll" ()
Private Sub Workbook_Open()
ChDrive Left$(Me.Path, 1)
ChDir Me.Path
Dummy
End Sub

You can use LoadLibrary api.
For example in my projects the code looks like this:
If LibraryLoaded() Then
Call MyFunc ...
End If
Public Function LibraryLoaded() As Boolean
Static IsLoaded As Boolean
Static TriedToLoadAlready As Boolean
If TriedToLoadAlready Then
LibraryLoaded = IsLoaded
Exit Function
End If
Dim path As String
path = VBAProject.ThisWorkbook.path
path = Left(path, InStrRev(path, "\") - 1)
IsLoaded = LoadLibrary(path & "\bin\" & cLibraryName)
TriedToLoadAlready = True
LibraryLoaded = IsLoaded
End Function

There is another really really ugly solution, but this blogger figured it out, and I can't figure out any other way:
http://blogs.msdn.com/pranavwagh/archive/2006/08/30/How-To-Load-Win32-dlls-Dynamically-In-VBA.aspx
Basically, you write a procedure that creates a code module in VBA during runtime. This module must create a reference to the dll and it must create a dummy function (or procedure) as part of this module that calls the dll. Then, from your code, you use Application.Run(dummyfunction(), arg1, arg2...). This is necessary because otherwise, the project will not compile because dummyfunction isn't yet a function.
You'll notice in his code, he uses InputBox() to get the location of the .dll but obviously you could get the location from a range in the spreadsheet. The following code snippet may be useful.
Dim cm As CodeModule
Dim vbc As VBComponent
Set cm = Application.VBE.ActiveVBProject.VBComponents.Add(vbext_ct_StdModule).CodeModule
cm.AddFromString (decString & funcString)
cm.Name = "MyNewModule"
Set vbc = cm.Parent
Application.VBE.ActiveVBProject.VBComponents.Remove vbc
'decString' and 'funcString' were just strings I constructed like his 'ss'. The snippet shows how you can rename the code module so that you could delete it later if needed. Obviously, this just deletes it right after it is created, and you probably wouldn't want to do that, but at least it shows you how it would be done.
Having said all that, we mostly just write .exe's now and shell out. If you need VBA to wait on the shell to finish, there are solutions for that issue as well.

Here's what I ended up doing, using Pranav Wagh's methodology linked above and code from C Pearson's site (http://www.cpearson.com/excel/vbe.aspx). This code prompts the user to select the path to the dll using an Open File window, builds a new module with a Declare Function with the inputted path and a function to execute a handshake with the dll. The purpose-built function in the dll returns a 1 if successful:
Public rtn As Integer
Sub LinkToDll()
Dim path As String, default As String
MsgBox "Select Geo_DLL.dll file from next window"
With Application.FileDialog(msoFileDialogOpen)
.AllowMultiSelect = False
.Title = "Select Geo_DLL.dll file"
If .Show = True Then
path = .SelectedItems(1)
End If
End With
'Add a module
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Set VBProj = ActiveWorkbook.VBProject
Set VBComp = VBProj.VBComponents.Add(vbext_ct_StdModule)
VBComp.Name = "LinkModule"
'Add procedure to module
Dim CodeMod As VBIDE.CodeModule
Dim LineNum As Long
Set VBComp = VBProj.VBComponents("LinkModule")
Set CodeMod = VBComp.CodeModule
With CodeMod
LineNum = .CountOfLines + 1
.InsertLines LineNum, "Declare Function RegDll Lib " & Chr(34) & path & Chr(34) & " (ByRef rtn As Integer)"
LineNum = LineNum + 1
.InsertLines LineNum, "Sub runthisfunc(rtn)"
LineNum = LineNum + 1
.InsertLines LineNum, "On Error Resume Next"
LineNum = LineNum + 1
.InsertLines LineNum, "rtn = 0"
LineNum = LineNum + 1
.InsertLines LineNum, "RegDll rtn"
LineNum = LineNum + 1
.InsertLines LineNum, "If rtn = 1 Then MsgBox (" & Chr(34) & "DLL linked" & Chr(34) & ")"
LineNum = LineNum + 1
.InsertLines LineNum, "If rtn = 0 Then MsgBox (" & Chr(34) & "DLL not found" & Chr(34) & ")"
LineNum = LineNum + 1
.InsertLines LineNum, "End Sub"
End With
'This is what CodeMod.InsertLines is writing:
'--------------------------------------------
'Declare Function RegDll Lib "C:\path\Geo_DLL.dll" (ByRef rtn As Integer)
'Sub runthisfunc(rtn)
'On Error Resume Next
'rtn = 0
'RegDll rtn
'If rtn = 1 Then MsgBox ("DLL Linked")
'If rtn = 0 Then MsgBox (DLL not found")
'End Sub
Application.Run "runthisfunc", rtn
'Delete Module
VBProj.VBComponents.Remove VBComp
End Sub
However, once I turned the workbook (xlsm) into an addin (xlam) I found that Excel wouldn't let the macro create new modules so my LinkToDll wouldn't work. The fix was to put the Declare Function back into LinkToDll with just the dll file name ("Geo_DLL.dll") as the Lib along with the runthisfunc sub. I found having the user simply select the dll file via the Open File window was enough to point Excel to the dll even with only the file name in the Lib portion of the Declare Function statement.
Chris

In my case code below worked. I added "ChDir (ThisWorkbook.Path)"
after function. But I tested it only on my laptop. I don't know if it works on network.
Option Explicit
' Declare the function that is in the DLL
Private Declare PtrSafe Function suntransitForEXL Lib _
"sampadll.dll" (ByRef lat As Double, ByRef lon As Double, ByRef dy As Integer, ByRef mnt As Integer, ByRef yr As Integer, ByRef tmz As Double) As Double
' use function on worksheet
Function noon(latitude As Double, longtitude As Double, day As Integer, month As Integer, year As Integer, timezone As Double) As Double
ChDir (ThisWorkbook.Path) ' Set working directory to current.
Dim decimaltime As Double
Dim hour As Integer
Dim minute As Integer
Dim second As Integer
decimaltime = suntransitForEXL(latitude, longtitude, day, month, year, timezone)
hour = Fix(decimaltime)
minute = Fix((decimaltime - hour) * 60)
second = Fix(((decimaltime - hour) * 60 - minute) * 60)
noon = TimeSerial(hour, minute, second)
End Function

Related

VBA - Unable to map drive to sharepoint on another computer

I'm mapping to the company's sharepoint drive using VBA. The intention is to save local file to sharepoint, and delete local file and unmapped the drive after success.
On my machine(Windows 10 64bits), the code works perfectly fine, successfully mapped the drive, created folder and file, successfully uploaded to sharepoint and unmap the drive.
However, when I run the same excel workbook that contains the same code on my colleague's computer(Window 7), it failed. There's no error being shown, except that it keeps on loading and loading until Excel Not Responsive. I tried manually mapping the drive, it success.
I tried to debug and found out that the code stops (keeps on loading) at MsgBox "Hello" but could not figure out what's missing.
Both are using Excel 2016
Any help and suggestions are appreciated. let me know if more info is needed. Thanks in advance.
This is my vba code
Sub imgClicked()
Dim fileName As String
Dim SharePointLib As String
Dim MyPath As String
Dim folderPath As String
Dim objNet As Object
Dim copyPath As String
Dim copyFilePath As String
folderPath = Application.ThisWorkbook.path
MyPath = Application.ThisWorkbook.FullName
Dim objFSO As Object
Dim strMappedDriveLetter As String
Dim strPath As String
Dim spPath As String
strPath = "https://company.com/sites/test/test 123/" 'example path
spPath = AvailableDriveLetter + ":\test.xlsm" 'example path
copyPath = folderPath + "\copyPath\"
'Add reference if missing
Call AddReference
Set objFSO = CreateObject("Scripting.FileSystemObject")
With objFSO
strMappedDriveLetter = IsAlreadyMapped(.GetParentFolderName(strPath))
If Not Len(strMappedDriveLetter) > 0 Then
strMappedDriveLetter = AvailableDriveLetter
If Not MapDrive(strMappedDriveLetter, .GetParentFolderName(strPath)) Then
MsgBox "Failed to map SharePoint directory", vbInformation, "Drive Mapping Failure"
Exit Sub
End If
End If
' Check file/folder path If statement here
End With
Set objFSO = Nothing
End Sub
Code for getting available drive
' Returns the available drive letter starting from Z
Public Function AvailableDriveLetter() As String
' Returns the last available (unmapped) drive letter, working backwards from Z:
Dim objFSO As Object
Dim i As Long
Set objFSO = CreateObject("Scripting.FileSystemObject")
For i = Asc("Z") To Asc("A") Step -1
Select Case objFSO.DriveExists(Chr(i))
Case True
Case False
Select Case Chr(i)
Case "C", "D" ' Not actually necessary - .DriveExists should return True anyway...
Case Else
AvailableDriveLetter = Chr(i)
Exit For
End Select
End Select
Next i
Set objFSO = Nothing
MsgBox "This is the next available drive: " + AvailableDriveLetter ' returns Z drive
MsgBox "Hello" ' After this msgBox, starts loading until Not Responsive
End Function
Function to Map drive
Public Function MapDrive(strDriveLetter As String, strDrivePath As String) As Boolean
Dim objNetwork As Object
If Len(IsAlreadyMapped(strDrivePath)) > 0 Then Exit Function
Set objNetwork = CreateObject("WScript.Network")
objNetwork.MapNetworkDrive strDriveLetter & ":", strDrivePath, False
MapDrive = True
MsgBox "Successfully Created the Drive!"
Set objNetwork = Nothing
End Function
Code for MappedDrive
Public Function GetMappedDrives() As Variant
' Returns a 2-D array of (1) drive letters and (2) network paths of all mapped drives on the users machine
Dim objFSO As Object
Dim objDrive As Object
Dim arrMappedDrives() As Variant
Dim i As Long
Set objFSO = CreateObject("Scripting.FileSystemObject")
ReDim arrMappedDrives(1 To 2, 1 To 1)
For i = Asc("A") To Asc("Z")
If objFSO.DriveExists(Chr(i)) Then
Set objDrive = objFSO.GetDrive(Chr(i))
If Not IsEmpty(arrMappedDrives(1, UBound(arrMappedDrives, 2))) Then
ReDim Preserve arrMappedDrives(1 To 2, 1 To UBound(arrMappedDrives, 2) + 1)
End If
arrMappedDrives(1, UBound(arrMappedDrives, 2)) = Chr(i) ' Could also use objDrive.DriveLetter...
arrMappedDrives(2, UBound(arrMappedDrives, 2)) = objDrive.ShareName
End If
Next i
GetMappedDrives = arrMappedDrives
Set objDrive = Nothing
Set objFSO = Nothing
End Function
Public Function IsAlreadyMapped(strPath As String) As String
' Tests if a given network path is already mapped on the users machine
' (Returns corresponding drive letter or ZLS if not found)
Dim strMappedDrives() As Variant
Dim i As Long
strMappedDrives = GetMappedDrives
For i = LBound(strMappedDrives, 2) To UBound(strMappedDrives, 2)
If LCase(strMappedDrives(2, i)) Like LCase(strPath) Then
IsAlreadyMapped = strMappedDrives(1, i)
Exit For
End If
Next i
Set objNetwork = Nothing
End Function
Add Reference
Sub AddReference()
'Macro purpose: To add a reference to the project using the GUID for the
'reference library
Dim strGUID As String, theRef As Variant, i As Long
'Update the GUID you need below.
strGUID = "{420B2830-E718-11CF-893D-00A0C9054228}"
'Set to continue in case of error
On Error Resume Next
'Remove any missing references
For i = ThisWorkbook.VBProject.References.Count To 1 Step -1
Set theRef = ThisWorkbook.VBProject.References.Item(i)
If theRef.isbroken = True Then
ThisWorkbook.VBProject.References.Remove theRef
End If
Next i
'Clear any errors so that error trapping for GUID additions can be evaluated
Err.Clear
'Add the reference
ThisWorkbook.VBProject.References.AddFromGuid _
GUID:=strGUID, Major:=1, Minor:=0
'If an error was encountered, inform the user
Select Case Err.Number
Case Is = 32813
'Reference already in use. No action necessary
Case Is = vbNullString
'Reference added without issue
Case Else
'An unknown error was encountered, so alert the user
MsgBox "A problem was encountered trying to" & vbNewLine _
& "add or remove a reference in this file" & vbNewLine & "Please check the " _
& "references in your VBA project!", vbCritical + vbOKOnly, "Error!"
End Select
On Error GoTo 0
End Sub
Procedure imgClicked is calling function AvailableDriveLetter multiple times. Remember that the function has to execute each time you refer to it.
I ran imgClicked (assuming that's the procedure you start with) and I was told, twice, "Next available letter = Z" and "Hello" and then it crashed Excel (perhaps getting stuck in a loop of creating FileSystem objects to look for an available drive letter?)
Try assigning AvailableDriveLetter to a variable (string) at the beginning of the procedure and referring to the variable each time you need the value, and see if you still have the issue.
(Remember to save before execution -- I get frustrated when troubleshooting "application hanging" issues because I keep forgetting to save my changes and then lose them on the crash!)
If this doesn't work, add a breakpoint (F9) on the End Function line after your "Hello" box and see if the code stops there. (I have trouble believing the MsgBox or End Function are the culprit.) If not, which procedure runs after that?
One more thing whether the issue is resolved or not:
Add Option Explicit at the very beginning of your module and then Compile the project and fix your missing variable declaration(s).
This is recommended whenever troubleshooting an issue as a means to eliminate variable declaration issues as a possible cause.

Word VBA causing issues in template

I have a Word 2010 template with fields, and drop down lists etc and a save button to save the document in a certain place with a certain name. Part of the file name I retrieve as the network username in VBA and another part of the file name is the Date. This works fine for me but when I attempt to test the document with another user the VBA code complains at the line below stating "Compile error: can't find project or library".
strUserName = (Environ$("username"))
If I changed the above to be like the line below instead and another user opens the template and clicks the save button
strUserName = "validnetworkname"
It then complains with the same error at the next VBA referencing which is
strDate = Date
What is wrong here please?
I use this function:
Private Declare Function apiGetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Public Function UserName() As String
On Error GoTo ErrProc
Dim lnglen As Long
lnglen = 255
Dim strSpace As String
strSpace = String(254, 0)
Dim lngX As Long
lngX = apiGetUserName(strSpace, lnglen)
If lngX <> 0 Then GetUserName = Left(strSpace, lnglen - 1)
Leave:
On Error GoTo 0
Exit Function
ErrProc:
Resume Leave
End Function
To call it:
Dim user_ As String
user_ = UserName

Check if Private Sub Workbook.open() is empty

I have a user who needs to execute a macro after an Excel file was opened, and who needs to know (programatically) if the current Excel file's Private Sub Workbook.open() routine is empty.
Is there any way to keep this information in memory after the workbook is opened so that if the user needs to run his macro this information is available. Something along a persistent global var would be ideal. But i'm not sure if it's possible.
Thanks!
This code below (inside a regular module) loops through all the VB Project components (including ThisWorkbook module), and checks if the module name is "ThisWorkbook".
Once it finds "ThisWorkbook" module, it checks the total number of code lines inside that module, if it's 0, it raises a MsgBox that it's empty. If it's not, then it checks to see if it can find a "Workbook_Open" string inside the code. If it does, it counts the total number of lines (not empty lines) of code between the "Workbook_Open" line and the closest "End Sub" line.
Check_WorkBookModule_Contents Code
Option Explicit
Sub Check_WorkBookModule_Contents()
Const PROC_NAME = "ThisWorkbook"
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
Dim CodeMod As VBIDE.CodeModule
Dim i As Long, j As Long, SubLinesCount As Long
Dim ModuleCodeLinesCount As Long
Set VBProj = ActiveWorkbook.VBProject
' loop through all modules, worksheets and other objects in VB Project
For Each VBComp In VBProj.VBComponents
Set CodeMod = VBComp.CodeModule
Debug.Print CodeMod.Name ' <-- for debug
If CodeMod.Name Like PROC_NAME Then ' <-- check if module name is "ThisWorkbook"
' if total of code lines in "ThisWorkbook" module is empty
If CodeMod.CountOfLines = 0 Then
MsgBox CodeMod.Name & " module is empty"
Exit Sub
End If
SubLinesCount = 0 ' reset counter
' loop through all code lines inside current module
For i = 1 To CodeMod.CountOfLines
If Len(CodeMod.Lines(i, 1)) > 0 Then
' if the name of current sub is found within the current code line
If CodeMod.Lines(i, 1) Like "*Workbook_Open*" Then
For j = i + 1 To CodeMod.CountOfLines
If Len(CodeMod.Lines(j, 1)) > 0 And Not CodeMod.Lines(j, 1) Like "End Sub*" Then
SubLinesCount = SubLinesCount + 1
End If
Next j
If SubLinesCount > 0 Then
MsgBox CodeMod & " module, has an event of 'Workbook_Open' , with total of " & SubLinesCount & " lines of code"
Exit Sub
Else
MsgBox CodeMod & " module, has an event of 'Workbook_Open' , but it's empty !"
Exit Sub
End If
End If
End If
Next i
End If
Next VBComp
End Sub
Note: In order to access the VB Project Module, you need to follow the 2 steps below:
Step 1: Add "Trust access to the VBA project object model" , go to Developer >> Macro Security >> then add a V to the Trust access to the VBA project object model.
Step 2: Add Reference to your VB project, add "Microsoft Visual Basic for Applications Extensibility 5.3"

How to prevent free distribution of a commercial Excel spreadsheet

I'm not sure if this is more appropriate under a different SE site (Super User?).
I want to build and sell a complex macro driven driven spreadsheet to a certain vertical. I am mainly concerned about free/unauthorised distribution between customers within that vertical.
I can see that there is a few obscure products on the market that might be able to do what I want, but the few reviews that i've been able to find haven't been favourable.
One vendor however lists that free distribution can circumvented by either:
Using a key generator to create license codes
Using the online activation feature
Or by simply using an encrypted password
Is anyone aware of any guidelines/frameworks (any language) for me to build my own solution to achieve this, namely requiring licence codes or online activation?
If this is generally a difficult endeavour, is there a commercial product that anyone recommend?
I'm also thinking the complexities involved in achieving this might push me to building a small SaaS application instead. Am I better off just going that route?
I have created an Excel sheet that I could remotely remove access to if a monthly subscription payment failed. Here is how to accomplish this:
Create and HTML table and upload it to your website
Within your Excel doc go to the data tab and select get from web - import your table into a sheet called "Verify" - make sure your table has 3 columns. Serial Number is in the first column, description of user in 2nd, and your error message in the top of col 3. The error message stored here is what every user that isn't registered will see. The first serial number should appear in cell A2 of the sheet Verify.
Within your Visual Basic editor paste this code into a Module - This code will return an 8 digit serial number based on a PC's Hard Drive serial number:
Function HDSerialNumber() As String
Dim fsObj As Object
Dim drv As Object
Set fsObj = CreateObject("Scripting.FileSystemObject")
Set drv = fsObj.Drives("C")
HDSerialNumber = Left(Hex(drv.SerialNumber), 4) _
& "-" & Right(Hex(drv.SerialNumber), 4)
End Function
Also in another module I make sure the Internet is connected. If no Internet then the sheet closes. If you don't do this then if someone disconnects from the Internet your serials won't be loaded.
Option Explicit
#If VBA7 And Win64 Then
Private Declare PtrSafe Function InternetGetConnectedStateEx Lib "wininet.dll" (ByRef lpdwFlags As Long, ByVal lpszConnectionName As String, ByVal dwNameLen As Integer, ByVal dwReserved As Long) As Long
#Else
Private Declare Function InternetGetConnectedStateEx Lib "wininet.dll" (ByRef lpdwFlags As Long, ByVal lpszConnectionName As String, ByVal dwNameLen As Integer, ByVal dwReserved As Long) As Long
#End If
Function IsInternetConnected() As Boolean
Dim strConnType As String, lngReturnStatus As Long, MyScript As String
If Application.OperatingSystem Like "*Macintosh*" Then
MyScript = "repeat with i from 1 to 2" & vbNewLine
MyScript = MyScript & "try" & vbNewLine
MyScript = MyScript & "do shell script ""ping -o -t 2 www.apple.com""" & vbNewLine
MyScript = MyScript & "set mystatus to 1" & vbNewLine
MyScript = MyScript & "exit repeat" & vbNewLine
MyScript = MyScript & "on error" & vbNewLine
MyScript = MyScript & "If i = 2 Then set mystatus to 0" & vbNewLine
MyScript = MyScript & "end try" & vbNewLine
MyScript = MyScript & "end repeat" & vbNewLine
MyScript = MyScript & "return mystatus"
If MacScript(MyScript) Then IsInternetConnected = True
Else
lngReturnStatus = InternetGetConnectedStateEx(lngReturnStatus, strConnType, 254, 0)
If lngReturnStatus = 1 Then IsInternetConnected = True
End If
End Function
Then inside the Workbook_Open area paste this:
Private Sub Workbook_Open()
If IsInternetConnected Then
Dim objFSO As Object
Dim MyFolder As String
Dim sFileName As String
Dim iFileNum As Integer
Dim sBuf As String
Dim trialstartdate As String
Dim z As String
Dim fsoFSO
Set fsoFSO = CreateObject("Scripting.FileSystemObject")
'UNCOMMENT below to SHOW the serials sheet when the workbook is opened
ActiveWorkbook.Sheets("Verify").Visible = xlSheetVisible
'UNCOMMENT below to hide the serials sheet when the workbook is opened
'ActiveWorkbook.Sheets("Verify").Visible = xlSheetVeryHidden
Refresh_Serials
z = 2
'loop here for valid hard drive serial number
Do Until IsEmpty(Worksheets("Verify").Cells(z, 1).Value)
If Worksheets("Verify").Cells(z, 1).Value = HDSerialNumber Then
'verified and let pass
GoTo SerialVerified
End If
z = z + 1
Loop
Dim custommessage As String
custommessage = Worksheets("Verify").Cells(2, 3)
MsgBox custommessage + " Your serial number is: " + HDSerialNumber
Dim wsh1, MyKey1
Set wsh1 = CreateObject("Wscript.Shell")
MyKey1 = "%{TAB}"
wsh1.SendKeys MyKey1
MsgBox "The Commission Tracker will not open without a valid serial number. It will now close. uncomment this in workbook->open to close the workbook if the serial isn't found"
Application.DisplayAlerts = False
'uncomment this to close the workbook if the serial isn't found
'ActiveWorkbook.Close
Application.DisplayAlerts = True
SerialVerified:
' does the end user agree to not use this tool for mailicous purposes?
MsgAgree = MsgBox("Your PC's serial number is " & HDSerialNumber & ". By clicking 'Yes' you agree to use our software as described in our end user agreement. - the URL to your terms here", vbYesNo, "Final Agreement")
If MsgAgree = vbNo Then
'close program
MsgBox "This program will now close since you do not agree to our end user agreement"
Application.DisplayAlerts = False
ActiveWorkbook.Close
Application.DisplayAlerts = True
Else
'continue to open the program
End If
Else
MsgBox "No Network Connection Detected - You must have an internet connection to run the commission tracker."
Application.DisplayAlerts = False
ActiveWorkbook.Close
Application.DisplayAlerts = True
End If
End Sub
That should do it....
Create your own special unique license keys in a macro that will unlikely be generated in a key generator. Add your own prefix, for example. You could store if a user is using it in an online database. Downfall to this solution is that the users would have to be connected to the outside internet.
Then lock down that module with the keys by the following:
To protect your code, open the Excel Workbook and go to Tools>Macro>Visual Basic Editor (Alt+F11). Now, from within the VBE go to Tools>VBAProject Properties and then click the Protection page tab and then check "Lock project from viewing" and then enter your password and again to confirm it. After doing this you must save, close & reopen the Workbook for the protection to take effect.

Source control of Excel VBA code modules

I'd like to be able to source control my Excel spreadsheet's VBA modules (currently using Excel 2003 SP3) so that I can share and manage the code used by a bunch of different spreadsheets - and therefore I'd like to re-load them from files when the spreadsheet is opened.
I've got a module called Loader.bas, that I use to do most of the donkey work (loading and unloading any other modules that are required) - and I'd like to be able to load it up from a file as soon as the spreadsheet is opened.
I've attached the following code to the Workbook_Open event (in the ThisWorkbook class).
Private Sub Workbook_Open()
Call RemoveLoader
Call LoadLoader
End Sub
Where RemoveLoader (also within the ThisWorkbook class) contains the following code:
Private Sub RemoveLoader()
Dim y As Integer
Dim OldModules, NumModules As Integer
Dim CompName As String
With ThisWorkbook.VBProject
NumModules = ThisWorkbook.VBProject.VBComponents.Count
y = 1
While y <= NumModules
If .VBComponents.Item(y).Type = 1 Then
CompName = .VBComponents.Item(y).Name
If VBA.Strings.InStr(CompName, "Loader") > 0 Then
OldModules = ThisWorkbook.VBProject.VBComponents.Count
.VBComponents.Remove .VBComponents(CompName)
NumModules = ThisWorkbook.VBProject.VBComponents.Count
If OldModules - NumModules = 1 Then
y = 1
Else
MsgBox ("Failed to remove " & CompName & " module from VBA project")
End If
End If
End If
y = y + 1
Wend
End With
End Sub
Which is probably a bit overcomplicated and slightly crude - but I'm trying everything I can find to get it to load the external module!
Often, when I open the spreadsheet, the RemoveLoader function finds that there's a "Loader1" module already included in the VBA project that it is unable to remove, and it also fails to load the new Loader module from the file.
Any ideas if what I'm trying to do is possible? Excel seems very fond of appending a 1 to these module names - either when loading or removing (I'm not sure which).
There is an excellent solution to the vba version control problem here: https://github.com/hilkoc/vbaDeveloper
The nice part about this is that it exports your code automatically, as soon as you save your workbook. Also, when you open a workbook, it imports the code.
You don't need to run any build scripts or maven commands and you don't need to make any changes to your workbooks. It works for all.
It has also solved the import problem where modules such as ModName are being imported as ModName1 into a duplicate module. The importing works as it should, even when doing it multiple times.
As a bonus, it comes with a simple code formatter, that allows you to format your vba code as you write it within the VBA Editor.
Look at the VBAMaven page. I have a homegrown solution that uses the same concepts. I have a common library with a bunch of source code, an ant build and an 'import' VB script. Ant controls the build, which takes a blank excel file and pushes the needed code into it. #Mike is absolutely correct - any duplicate module definitions will automatically have a number appended to the module name. Also, class modules (as in Sheet and ThisWorkbook) classes require special treatment. You can't create those modules, you have to read the input file and write the buffer into the appropriate module. This is the VB script I currently use to do this. The section containing # delimited text (i.e. #build file#) are placeholders - the ant build replaces these tags with meaningful content. It's not perfect, but works for me.
''
' Imports VB Basic module and class files from the src folder
' into the excel file stored in the bin folder.
'
Option Explicit
Dim pFileSystem, pFolder, pPath
Dim pShell
Dim pApp, book
Dim pFileName
pFileName = "#build file#"
Set pFileSystem = CreateObject("Scripting.FileSystemObject")
Set pShell = CreateObject("WScript.Shell")
pPath = pShell.CurrentDirectory
If IsExcelFile (pFileName) Then
Set pApp = WScript.CreateObject ("Excel.Application")
pApp.Visible = False
Set book = pApp.Workbooks.Open(pPath & "\build\" & pFileName)
Else
Set pApp = WScript.CreateObject ("Word.Application")
pApp.Visible = False
Set book = pApp.Documents.Open(pPath & "\build\" & pFileName)
End If
'Include root source folder code if no args set
If Wscript.Arguments.Count = 0 Then
Set pFolder = pFileSystem.GetFolder(pPath & "\src")
ImportFiles pFolder, book
'
' Get selected modules from the Common Library, if any
#common path##common file#
Else
'Add code from subdirectories of src . . .
If Wscript.Arguments(0) <> "" Then
Set pFolder = pFileSystem.GetFolder(pPath & "\src\" & Wscript.Arguments(0))
ImportFiles pFolder, book
End If
End If
Set pFolder = Nothing
Set pFileSystem = Nothing
Set pShell = Nothing
If IsExcelFile (pFileName) Then
pApp.ActiveWorkbook.Save
Else
pApp.ActiveDocument.Save
End If
pApp.Quit
Set book = Nothing
Set pApp = Nothing
'' Loops through all the .bas or .cls files in srcFolder
' and calls InsertVBComponent to insert it into the workbook wb.
'
Sub ImportFiles(ByVal srcFolder, ByVal obj)
Dim fileCollection, pFile
Set fileCollection = srcFolder.Files
For Each pFile in fileCollection
If Right(pFile, 3) = "bas _
Or Right(pFile, 3) = "cls _
Or Right(pFile, 3) = "frm Then
InsertVBComponent obj, pFile
End If
Next
Set fileCollection = Nothing
End Sub
'' Inserts the contents of CompFileName as a new component in
' a Workbook or Document object.
'
' If a class file begins with "Sheet", then the code is
' copied into the appropriate code module 1 painful line at a time.
'
' CompFileName must be a valid VBA component (class or module)
Sub InsertVBComponent(ByVal obj, ByVal CompFileName)
Dim t, mName
t = Split(CompFileName, "\")
mName = Split(t(UBound(t)), ".")
If IsSheetCodeModule(mName(0), CompFileName) = True Then
ImportCodeModule obj.VBProject.VBComponents(mName(0)).CodeModule, _
CompFileName
Else
If Not obj Is Nothing Then
obj.VBProject.VBComponents.Import CompFileName
Else
WScript.Echo "Failed to import " & CompFileName
End If
End If
End Sub
''
' Imports the code in the file fName into the workbook object
' referenced by mName.
' #param target destination CodeModule object in the excel file
' #param fName file system file containing code to be imported
Sub ImportCodeModule (ByVal target, ByVal fName)
Dim shtModule, code, buf
Dim fso
Set fso = CreateObject("Scripting.FileSystemObject")
Const ForReading = 1, ForWriting = 2, ForAppending = 3
Const TristateUseDefault = -2, TristateTrue = -1, TristateFalse = 0
Set buf = fso.OpenTextFile(fName, ForReading, False, TristateUseDefault)
buf.SkipLine
code = buf.ReadAll
target.InsertLines 1, code
Set fso = Nothing
End Sub
''
' Returns true if the code module in the file fName
' appears to be a code module for a worksheet.
Function IsSheetCodeModule (ByVal mName, ByVal fName)
IsSheetCodeModule = False
If mName = "ThisWorkbook" Then
IsSheetCodeModule = False
ElseIf Left(mName, 5) = "Sheet" And _
IsNumeric(Mid (mName, 6, 1)) And _
Right(fName, 3) = "cls Then
IsSheetCodeModule = True
End If
End Function
''
' Returns true if fName has a xls file extension
Function IsExcelFile (ByVal fName)
If Right(fName, 3) = "xls" Then
IsExcelFile = True
Else
IsExcelFile = False
End If
End Function
I've been working on exactly this for months. I think I figured it out.
If the VB Project is trying to remove a module containing something in the call stack, it delays the removal until the call stack pops the module being replaced.
To avoid a module being in the call stack, launch your code with Application.OnTime
Private Sub Workbook_Open()
'WAS: module_library (1)
Application.OnTime (Now + TimeValue("00:00:01")), "load_library_kicker_firstiter"
End Sub
If you are self-healing your code like I am, you'll also have to launch your code that overwrites the 'calling' code with that same strategy.
I did not perform extensive testing yet, I am in total celebration mode, but this gets me extremely close to straightforward 99.9% self-healing code within a standalone .xls file without any other tricks
Usually the "Loader1" thing happens when Excel is asked to import a module and a module already exists with the same name. So if you import "Loader", then load it again and you'll get "Loader1". This would be because Excel doesn't know (or maybe just doesn't care) if it's really the same thing or a new chunk of functionality that just happens have the same module name, so it imports it anyway.
I can't think of a perfect solution, but I think I'd be inclined to try putting the load/unload logic in an add-in - that Workbook_Open thing looks a little vulnerable and having it in all workbooks is going to be a huge pain if the code ever needs to change (never say never). The XLA logic might be more complex (trickier to trap the necessary events, for one thing) but at least it'll only exist in one place.
Can't leave comment to comment
There is an excellent solution to the vba version control problem
here: https://github.com/hilkoc/vbaDeveloper
About saving custom VBAProjects using this XLAM.
Try this in Build.bas:
'===============
Public Sub testImport()
Dim proj_name As String
Dim vbaProject As Object
'proj_name = "VBAProject"
'Set vbaProject = Application.VBE.VBProjects(proj_name)
Set vbaProject = Application.VBE.ActiveVBProject
proj_name = vbaProject.name
Build.importVbaCode vbaProject
End Sub
'===============
Public Sub testExport()
Dim proj_name As String
Dim vbaProject As Object
'proj_name = "VBAProject"
'Set vbaProject = Application.VBE.VBProjects(proj_name)
Set vbaProject = Application.VBE.ActiveVBProject
proj_name = vbaProject.name
Build.exportVbaCode vbaProject
End Sub
'===============
This will export/import Active VBA Project.
The following is an easy-to-implement answer if you don't need to export your VBA code automatically. Just Call the following sub and it will export (as text) the VBA code of the current active workbook in a subfolder named "VC_nameOfTheWorkBook". If your project is a .xlam, you need to temporarily set the IsAddin property to false. Then you can easily add the new subfolder to Git. It is a slight modification of the code found here made by Steve Jansen. For a more complete solution see Ron de Bruin post.
You need to set a reference to "Microsoft Visual Basic For Applications Extensibility 5.3" and to "Microsoft Scripting Runtime" in the VBE Editor.
Public Sub ExportVisualBasicCode()
Const Module = 1
Const ClassModule = 2
Const Form = 3
Const Document = 100
Const Padding = 24
Dim VBComponent As Object
Dim path As String
Dim directory As String
Dim extension As String
Dim fso As New FileSystemObject
directory = ActiveWorkbook.path & "\VC_" & fso.GetBaseName(ActiveWorkbook.Name)
If Not fso.FolderExists(directory) Then
Call fso.CreateFolder(directory)
End If
Set fso = Nothing
For Each VBComponent In ActiveWorkbook.VBProject.VBComponents
Select Case VBComponent.Type
Case ClassModule, Document
extension = ".cls"
Case Form
extension = ".frm"
Case Module
extension = ".bas"
Case Else
extension = ".txt"
End Select
On Error Resume Next
Err.Clear
path = directory & "\" & VBComponent.Name & extension
Call VBComponent.Export(path)
If Err.Number <> 0 Then
Call MsgBox("Failed to export " & VBComponent.Name & " to " & path, vbCritical)
Else
Debug.Print "Exported " & Left$(VBComponent.Name & ":" & Space(Padding), Padding) & path
End If
On Error GoTo 0
Next
End Sub