Configure the Excel workbook

In this section, how to set the workbook is explained. There are two approaches:

  • By using Excel environment variable

  • By using batch files

Define the directory and name the CDB as explained in subsection.

Set up the Environment Variable [PATH]

An already configured workbook is available by following:

C:\<sofistik_installation>\2022\SOFiSTiK 2022\interfaces\examples\vba\configure_workbook

Important

After starting Excel, macros have to be activated, if this option is not set by default. If a security warning occurs, please choose ‘’activate/accept macros’’.

Lets start by defining the workbook.

  • Open the C:\exampleFolder\exampleWorkbook.xlsm

  • Open the VBA editor

  • Open ThisWorkbook!!!

And copy the code given below:

Example: Set the DLL path to PATH environment variable
'For the shell execute library
#If VBA7 And Win64 Then
Private Declare PtrSafe Function ShellExecute _
Lib "shell32.dll" Alias "ShellExecuteA" ( _
ByVal hWnd As Long, _
ByVal Operation As String, _
ByVal Filename As String, _
Optional ByVal Parameters As String, _
Optional ByVal Directory As String, _
Optional ByVal WindowStyle As Long = vbMinimizedFocus _
) As Long
#Else
Private Declare Function ShellExecute _
Lib "shell32.dll" Alias "ShellExecuteA" ( _
ByVal hWnd As Long, _
ByVal Operation As String, _
ByVal Filename As String, _
Optional ByVal Parameters As String, _
Optional ByVal Directory As String, _
Optional ByVal WindowStyle As Long = vbMinimizedFocus _
) As Long
#End If

'For the analysisPath code - THIS IS VERY IMPORTANT
#If VBA7 And Win64 Then
Private Declare PtrSafe Function GetCommandLine& Lib "kernel32" Alias "GetCommandLineA" ()
Private Declare PtrSafe Function lstrlen Lib "kernel32" ( _
   ByVal str As Long) As Long
Private Declare PtrSafe Function lstrcpy Lib "kernel32" ( _
   ByVal dest As String, _
   ByVal src As Long) As Long
Private Declare PtrSafe Function GetEnvironmentVariable Lib "kernel32" Alias "GetEnvironmentVariableA" ( _
   ByVal lpName As String, _
   ByVal lpBuffer As String, _
   ByVal nSize As Long) As Long
Private Declare PtrSafe Function SetEnvironmentVariable Lib "kernel32" _
Alias "SetEnvironmentVariableA" (ByVal lpName As String, _
ByVal lpValue As String) As Long
#Else
Private Declare Function GetCommandLine& Lib "kernel32" Alias "GetCommandLineA" ()
Private Declare Function lstrlen Lib "kernel32" ( _
   ByVal str As Long) As Long
Private Declare Function lstrcpy Lib "kernel32" ( _
   ByVal dest As String, _
   ByVal src As Long) As Long
Private Declare Function GetEnvironmentVariable Lib "kernel32" _
Alias "GetEnvironmentVariableA" ( _
ByVal lpName As String, _
ByVal lpBuffer As String, _
ByVal nSize As Long) As Long
Private Declare Function SetEnvironmentVariable Lib "kernel32" _
Alias "SetEnvironmentVariableA" ( _
ByVal lpName As String, _
ByVal lpValue As String) As Long
#End If

Const HKEY_LOCAL_MACHINE = &H80000002
' Reads a REG_SZ value from the local computer's registry using WMI.
' Parameters:
'   RootKey - The registry hive (see https://msdn.microsoft.com/en-us/library/aa390788(VS.85).aspx for a list of possible values).
'   Key - The key that contains the desired value.
'   Value - The value that you want to get.
'   RegType - The registry bitness: 32 or 64.
'
Function ReadRegStr(RootKey, Key, Value, RegType)
   Dim oCtx, oLocator, oReg, oInParams, oOutParams, oOutValues
   Set oCtx = CreateObject("WbemScripting.SWbemNamedValueSet")
   oCtx.Add "__ProviderArchitecture", RegType
   Set oLocator = CreateObject("Wbemscripting.SWbemLocator")
   Set oReg = oLocator.ConnectServer("", "root\default", "", "", , , , oCtx).Get("StdRegProv")
   Set oInParams = oReg.Methods_("GetStringValue").InParameters
   oInParams.hDefKey = RootKey
   oInParams.sSubKeyName = Key
   oInParams.sValueName = Value

   If oReg.EnumKey(RootKey, Key, oOutValues, "") = 0 Then
      Set oOutParams = oReg.ExecMethod_("GetStringValue", oInParams, , oCtx)
      ReadRegStr = oOutParams.sValue
      If IsNull(ReadRegStr) Then ReadRegStr = ""
   Else
      ReadRegStr = ""
   End If
End Function

Public Function expandPath()
Dim Path As String
Dim analysisPath As String

   'Get the environment path and add the SOFiSTiK directory to "Path" variable
   Path = Environ("Path")
   analysisPath = ReadRegStr(HKEY_LOCAL_MACHINE, "SOFTWARE\SOFiSTiK\InstallLocation", "sofistik_2022", 64)
   #If VBA7 And Win64 Then
      If analysisPath <> "" Then analysisPath = analysisPath + "\interfaces\64bit"
   #Else
      If analysisPath <> "" Then analysisPath = analysisPath + "\interfaces\32bit"
   #End If

   If analysisPath = "" Then
      MsgBox "No installation for SOFiSTiK 2022 found."
      expandPath = False
      Exit Function
   End If

   'Add the SOFiSTiK dll path to Environment Variable
   Path = analysisPath + ";" + Path

   Dim lSuccess As Long

   lSuccess = SetEnvironmentVariable("Path", Path)
   'Check if successfully
   If lSuccess = 0 Then
      MsgBox "Der Aufruf der Funktion SetEnvironmentVariable ist fehlgeschlagen." & vbNewLine & _
               "Der von Err.LastDllError gelieferte Fehlercode ist " & CStr(Err.LastDllError), _
               vbCritical, _
               "SetEnvironmentVariable fehlgeschlagen"
      expandPath = False
   Else

      expandPath = True
   End If
End Function

'When the workbooks opens execute code below
Public Sub Workbook_Open()
   If (Not expandPath()) Then Return
End Sub

The idea is to add the path of the workbook to the ENVIRONMENT %PATH% variable.

In the function expandPath() the analysisPath is set up (environment %PATH% variable). In the code above VBA also checks what version of VBA and MS Office is used.

Now create a new Module and name it by a custom name. In the example we named it sof_dll. Copy next code into the Module.

Example: Load the functions from DLL
'Check if office 64bit and if using VBA7
#If VBA7 And Win64 Then
   Declare PtrSafe Function sof_cdb_init Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_init" _
               (ByVal name As String, ByVal InitType As Long) As Long
   Declare PtrSafe Sub sof_cdb_close Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_close" _
               (ByVal Index As Long)
   Declare PtrSafe Sub sof_cdb_msglevel Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_msglevel" _
               (ByVal Index As Long)
   Declare PtrSafe Sub sof_cdb_flush Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_flush" _
               (ByVal Index As Long)
   Declare PtrSafe Function sof_cdb_status Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_status" _
               (ByVal Index As Long) As Long
   Declare PtrSafe Sub sof_cdb_lock Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_lock" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long)
   Declare PtrSafe Sub sof_cdb_free Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_free" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long)
   Declare PtrSafe Sub sof_cdb_kenq Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_kenq" _
               (ByVal Index As Long, ByRef kwh As Long, ByRef kwl As Long, ByVal Richt As Long)
   Declare PtrSafe Function sof_cdb_kexist Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_kexist" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long) As Long
   Declare PtrSafe Function sof_cdb_getupdate Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_getupdate" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long) As Long
   Declare PtrSafe Function sof_cdb_get Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_get" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long, _
               ByRef data As Any, ByRef datalen As Long, ByVal pos As Long) As Long
   Declare PtrSafe Function sof_cdb_put Lib "sof_cdb_w-2022.dll" Alias "VB_sof_cdb_put" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long, _
                  ByRef data As Any, ByRef datalen As Long, ByVal pos As Long) As Long
   Declare PtrSafe Function AQU_GET_SECT Lib "sof_cdb_w-2022.dll" Alias "VB_AQU_GET_SECT" _
               (ByVal KW As Long, ByVal nr As Long, ByVal XABS As Single, _
               ByVal LFC As Long, ByRef IERG As Long, ByRef SERG As Single)
#End If
#If VBA7 And Win32 Then
   'If MS Office is 32bit and VBA7 then use
   Declare Function sof_cdb_init Lib "cdb_w31.dll" Alias "VB_sof_cdb_init" _
               (ByVal name As String, ByVal InitType As Long) As Long
   Declare Sub sof_cdb_close Lib "cdb_w31.dll" Alias "VB_sof_cdb_close" _
               (ByVal Index As Long)
   Declare Sub sof_cdb_msglevel Lib "cdb_w31.dll" Alias "VB_sof_cdb_msglevel" _
               (ByVal Index As Long)
   Declare Sub sof_cdb_flush Lib "cdb_w31.dll" Alias "VB_sof_cdb_flush" _
               (ByVal Index As Long)
   Declare Function sof_cdb_status Lib "cdb_w31.dll" Alias "VB_sof_cdb_status" _
               (ByVal Index As Long) As Long
   Declare Sub sof_cdb_lock Lib "cdb_w31.dll" Alias "VB_sof_cdb_lock" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long)
   Declare Sub sof_cdb_free Lib "cdb_w31.dll" Alias "VB_sof_cdb_free" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long)
   Declare Sub sof_cdb_kenq Lib "cdb_w31.dll" Alias "VB_sof_cdb_kenq" _
               (ByVal Index As Long, ByRef kwh As Long, ByRef kwl As Long, ByVal Richt As Long)
   Declare Function sof_cdb_kexist Lib "cdb_w31.dll" Alias "VB_sof_cdb_kexist" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long) As Long
   Declare Function sof_cdb_getupdate Lib "cdb_w31.dll" Alias "VB_sof_cdb_getupdate" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long) As Long
   Declare Function sof_cdb_get Lib "cdb_w31.dll" Alias "VB_sof_cdb_get" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long, _
               ByRef data As Any, ByRef datalen As Long, ByVal pos As Long) As Long
   Declare Function sof_cdb_put Lib "cdb_w31.dll" Alias "VB_sof_cdb_put" _
               (ByVal Index As Long, ByVal kwh As Long, ByVal kwl As Long, _
                  ByRef data As Any, ByRef datalen As Long, ByVal pos As Long) As Long
Declare Function AQU_GET_SECT Lib "cdb_w31.dll" Alias "VB_AQU_GET_SECT" _
               (ByVal KW As Long, ByVal nr As Long, ByVal XABS As Single, _
               ByVal LFC As Long, ByRef IERG As Long, ByRef SERG As Single)
#End If

To test if everything works, connect to CDB. An example how to connect to CDB is given below.

Configuring the Workbook by using Batch Files

To run the workbook and to make an access to the SOFiSTiK DLL create a batch file with the next code:

Code: Set environment variable via batch and then run XLSM file
set local
set path=C:\<sofistik_installation>\2022\SOFiSTiK 2022; ^
%path%
start "" "C:\exampleFolder\exampleWorkbook.xlsm"
exit

Hint

When using this method, all Excel programs must be closed when running the batch file and the Excel Workbook. This approach can lead to different bugs and is NOT recommended.