VBA Custom Command Line Arguments
So this is something that I've used in Excel to be able to pass in runtime parameters to a macro enabled workbook, in the example provided I'm passing a path for a csv file for later processing. The way that this has been set up (as you'll see from the code) is to run through the command line arguments presented, strip out the bits that we're interested in and set the values of any desired arguments to variables within the workbook. Note: this code isn't entirely original and the majority of the work was done by the participants on this thread.
Passing arguments
The format that this approach expects is a series of key/value pairs separated by a pipe | and serialised by forward slash, after "/e/" to denote that the custom arguments are starting. So something like this:
/e/Key1|Val1/Key2|Val2
Depending on how you're actually calling the sheet you'll need to do a few different things. From the command line you could use any of the follwing:
excel.exe "C:\tst.xlsm" /e/csvpath|C:\csPath\thing.csv excel C:\tst.xlsm /e/csvpath|C:\csPath\thing.csv
and from within .Net (C# in this instance), you'd want to put something down that looks like this:
Process.Start(@"excel", @"C:\tst.xlsm /e/csvpath|C:\csPath\thing.csv");
To the Code!
The actual code that you'll want to use is as follows; Paste the following into a module in your workbook so that it can be accessed from anywhere (although that said there's no reason not to put it in the workbook module along with the next chunk):
Option Base 0 Option Explicit Declare Function GetCommandLine Lib "kernel32" Alias "GetCommandLineW" () As Long Declare Function lstrlenW Lib "kernel32" (ByVal lpString As Long) As Long Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (MyDest As Any, MySource As Any, ByVal MySize As Long) Function CmdToSTr(Cmd As Long) As String Dim Buffer() As Byte Dim StrLen As Long If Cmd Then StrLen = lstrlenW(Cmd) * 2 If StrLen Then ReDim Buffer(0 To (StrLen - 1)) As Byte CopyMemory Buffer(0), ByVal Cmd, StrLen CmdToSTr = Buffer End If End If End Function
and then within your 'ThisWorkbook' object enter the following. It's pretty well commented so it will take you through what's being done but essentially the code will strip through the user defined arguments as it finds them and then if it finds a key that it's looking for it will store that value into the declared global variable. If you've got a lot of parameters that you're looking to pass then you can add to the if statements at the bottom. I'd also recommend commenting out the MsgBox lines unless you want the functionality to be very noisy!
Public CSVPath As String ' This sub will try and strip out any 'user command line arguments' that are formatted in the following way: ' excel.exe "ThisWSheetPath" /e/key|value [/key|value]... ' The first section dictates which application to use, ' The second (enclosed by double quotes) denotes ' after this use /e/ to begin the user arguments, these should be a key and value separated by a pipe ' for multiple parameters to be passed separate the pairs out with a forward slash: ' /e/csvpath|C:\file.csv/secondparm|secondval ' ' Example: excel.exe "C:\tst.xlsm" /e/csvpath|C:\csPath\thing.csv Private Sub Workbook_Open() Dim CmdRaw As Long Dim CmdLine As String Dim userName As String Dim userPass As String Dim v() As String CmdRaw = GetCommandLine CmdLine = CmdToSTr(CmdRaw) 'MsgBox CmdLine Dim rev As String Dim fn As Integer Dim UsrParms As String Dim SplitParms() As String Dim s As Integer ' Grab only the string that we're interested in after /e/ rev = StrReverse(CmdLine) fn = InStr(1, rev, "/e/", vbTextCompare) - 1 ' did we submit any command line params? If fn > 0 Then UsrParms = StrReverse(Left(rev, fn)) ' split our paramstring out along forward slashes SplitParms = Split(UsrParms, "/") For s = 0 To UBound(SplitParms) Dim kvp() As String kvp = Split(SplitParms(s), "|") ' Let's look at each one 'MsgBox "Key: " & kvp(0) & vbNewLine & " Value: " & kvp(1) If UCase(kvp(0)) = "CSVPATH" Then ' Do something with your found variable! CSVPath = kvp(1) End If Next s End If If SCVPath <> "" Then MsgBox CSVPath End Sub