Mutex freezing the whole app when using multithreading - multithreading

I have a vb6 multithreaded app working and i would like to use mutexes to protect data. The expected behavior is that when a thread tried to obtain a lock on an existing mutex, when the "WaitForSingleObject" function is called, that thread blocks until the mutex is signaled. What I am experiencing is the entire app freezes.
To duplicate my project, open VB6 and create a new Active X EXE. Create a module with default name. Place this code in it:
Option Explicit
Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Sub Main()
' this hack is necessary to ensure that we only 'create' the application window once..
Dim hwnd As Long
hwnd = FindWindow(vbNullString, "Form1")
If hwnd = 0 Then
Dim f As Form1
Set f = New Form1
f.Show
Set f = Nothing
End If
End Sub
Next create a class, with default name and add this code to it:
Option Explicit
Private Const INFINITE = -1&
Private Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000
Private Const SYNCHRONIZE As Long = &H100000
Private Const MUTANT_QUERY_STATE As Long = &H1
Private Const MUTANT_ALL_ACCESS As Long = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or MUTANT_QUERY_STATE)
Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long
Private Declare Function CreateMutex Lib "kernel32" Alias "CreateMutexA" (lpMutexAttributes As Any, ByVal bInitialOwner As Long, ByVal lpName As String) As Long
Private Declare Function OpenMutex Lib "kernel32" Alias "OpenMutexA" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal lpName As String) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function ReleaseMutex Lib "kernel32" (ByVal hMutex As Long) As Long
Private Const MUTEX_NAME As String = "mymutex"
Private m_hCurrentMutex As Long
Public Sub Class_Terminate()
Call ReleaseIt
End Sub
Public Sub LockIt(success As String)
Dim hMutex As Long
MsgBox "Lockit t:" & App.ThreadID
hMutex = OpenMutex(STANDARD_RIGHTS_REQUIRED, 0, MUTEX_NAME)
If hMutex <> 0 Then
Form1.Caption = "waiting on mutex"
MsgBox "waiting t:" & App.ThreadID
Dim res As Long
Do
'MsgWaitForMultipleObjects
res = WaitForSingleObject(hMutex, INFINITE)
DoEvents
Loop While res = -1
m_hCurrentMutex = hMutex
Else
Form1.Caption = "creating mutex"
m_hCurrentMutex = CreateMutex(ByVal 0&, 1, MUTEX_NAME)
End If
Form1.Caption = success
MsgBox success
End Sub
Public Sub ReleaseIt()
If m_hCurrentMutex <> 0 Then
Call ReleaseMutex(m_hCurrentMutex)
Call CloseHandle(m_hCurrentMutex)
m_hCurrentMutex = 0
End If
End Sub
Finally, in the main form, add 4 command buttons and this code:
Option Explicit
Dim c(1) As Class1
'Lock
Private Sub Command1_Click()
If c(0) Is Nothing Then Set c(0) = CreateObject("Project1.Class1")
Call c(0).LockIt("Object0")
End Sub
Private Sub Command2_Click()
If c(1) Is Nothing Then Set c(1) = CreateObject("Project1.Class1")
Call c(1).LockIt("Object1")
End Sub
'Free
Private Sub Command3_Click()
If c(0) Is Nothing Then Set c(0) = CreateObject("Project1.Class1")
Call c(0).ReleaseIt
End Sub
Private Sub Command4_Click()
If c(1) Is Nothing Then Set c(1) = CreateObject("Project1.Class1")
Call c(1).ReleaseIt
End Sub
Private Sub Form_Unload(Cancel As Integer)
Set c(0) = Nothing
Set c(1) = Nothing
End
End Sub
The first two command buttons lock their respective mutexes. The 2nd two free it. Notice how before the mutex is locked, a unique thread id is displayed. This made me believe only that thread should block, and not freeze the entire application.
Any assistance would be greatly appreciated. Thank you.
EDIT: I forgot to mention a very important part: In the project properties section, I have it set to create 'thread per object' and this is verified with results of the msghox App.ThreadID calls.

While you can make a class create another thread (Using the ActiveX EXE hack) that you still have a single execution thread, i.e. all calls are serialised.
If you want an asynchronous call cross thread, you need to set a timer (SetTimer() API) in that function and wait for the callback before doing the long running code. Also note that while that thread is locked you can not make ANY calls into it unless they can break and call DoEvents.

In order to avoid the locking of the app you should have somewhere in your application at least on call to CreateThread.
The problem is that all the code you have is executed on a single thread, the main app thread. So when you click the button the main thread will block in WaitForSingleObject until the mutex is released. Because the main thread is blocked, the UI of the application freezes (the message loop is blocked), so you are not able to click the other button in order to release the mutex.
EDIT: Even if every object has its own thread, it seems the calls to class methods are synchronized. This means that the calling thread (in your case the UI thread) will wait until the LockIt method ends, even if the code in LockIt method executes in another thread. You can easily check this by putting an MessageBox at the end of Command1_Click and Command2_Click. These message boxes will appear only after all the message boxes from LockIt are displayed, not immediately after you call the LockIt method. (I think it's better to replace the MessageBox with some kind of log messages saved to a file). As a conclusion it seems that you get the synchronization of threads as a default behavior, so probably you don't need to use mutexes.

Related

How to trap Left Click in Excel?

I want to know if the selection of a cell is caused by a cursor move or by a mouse action.
There are a lot of articles explaining how to trap mouse click in Excel, even some explaining that left click can be trapped.
This code is found many times on the web:
' The declaration tells VBA where to find and how to call the API
Private Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
' The function returns whether a key (or mouse button) is pressed or not
Public Function KeyPressed(ByVal Key As Long) As Boolean
KeyPressed = CBool((GetAsyncKeyState(Key) And &H8000) = &H8000)
End Function
Private Sub Worksheet_SelectionChange(ByVal Target As Range)
If (KeyPressed(&H1) = True) Then
MsgBox "Left click"
End If
If (KeyPressed(&H2) = True) Then
MsgBox "Right click"
End If
End Sub
This code traps the right click event, but not the left! Probably because it is placed in the Worksheet_SelectionChange event which is only called when a SelectionChanged has occurred and therefore when the left button has already been released!
How to detect a left click on a cell of a sheet to know if the selection of a cell is caused by a keyboard input (arrows or enter) or by a mouse left/right click action?
I found this great article and adapt it for mouse button check : https://www.mrexcel.com/board/threads/keypress-event-for-worksheet-cells.181654/
Add this module:
Option Explicit
Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
Declare Function CallNextHookEx Lib "user32" _
(ByVal hHook As Long, ByVal nCode As Long, ByVal wParam As Long, lParam As Any) As Long
Declare Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As Long) As Long
Declare Function GetActiveWindow Lib "user32" () As Long
Declare Function FindWindow Lib "user32" Alias "FindWindowA" _
(ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Const HC_ACTION = 0
Const WH_MOUSE_LL = 14 ' Type of windows message to be hooked
Const WM_RBUTTONDOWN = &H204 ' Mouse message for right button down
Const WM_LBUTTONDOWN = &H201 ' Mouse message for left button down
Type KBDLLHOOKSTRUCT
vkCode As Long
scanCode As Long
flags As Long
time As Long
dwExtraInfo As Long
End Type
Dim hkLowLevelID As Long ' Hook id of the LowLevelMouseProc function
Dim LeftMouseDown As Boolean ' Flag to trap left mouse down events
Dim RightMouseDown As Boolean ' Flag to trap left mouse down events
Dim EllapsedTimer As Date
Function LowLevelMouseProc _
(ByVal nCode As Long, ByVal wParam As Long, lParam As KBDLLHOOKSTRUCT) As Long
On Error GoTo ResumeHere
' CAUTION !!!
' We can't do any action which envolves UI interaction because Excel is already beeing to update UI
' Hook mouse events only if XL is the active window
If GetActiveWindow = FindWindow("XLMAIN", Application.Caption) Then
If (nCode = HC_ACTION) Then
' Check if the left button is pressed
If (wParam = WM_LBUTTONDOWN) Then
LeftMouseDown = True
EllapsedTimer = Now() + TimeValue("00:00:01")
Application.OnTime EllapsedTimer, "ResetFlags"
ElseIf (wParam = WM_RBUTTONDOWN) Then
RightMouseDown = True
EllapsedTimer = Now() + TimeValue("00:00:01")
Application.OnTime EllapsedTimer, "ResetFlags"
End If
End If
End If
ResumeHere:
' Pass function to next hook if there is one
LowLevelMouseProc = CallNextHookEx(0, nCode, wParam, ByVal lParam)
End Function
Function isLeftMouseDown()
isLeftMouseDown = LeftMouseDown
End Function
Function isRightMouseDown()
isRightMouseDown = RightMouseDown
End Function
' Reset the flags if the click has been thrown too long ago
Sub ResetFlags()
RightMouseDown = False
LeftMouseDown = False
End Sub
' Call this proc when opening Workbook
Sub StartHook()
If (hkLowLevelID = 0) Then
' Initiate the hooking process
hkLowLevelID = SetWindowsHookEx(WH_MOUSE_LL, AddressOf LowLevelMouseProc, Application.Hinstance, 0)
End If
End Sub
' Call this proc when closing Workbook
Sub StopHook()
If hkLowLevelID <> 0 Then
UnhookWindowsHookEx hkLowLevelID
hkLowLevelID = 0
End If
End Sub
It defines 2 procs StartHook and StopHook that you use in "ThisWoorkbook":
Private Sub Workbook_Open()
Call StartHook
End Sub
Private Sub Workbook_BeforeClose(Cancel As Boolean)
Call StopHook
End Sub
And 2 functions that you can use in the macro for the Sheets like this:
Private Sub Worksheet_SelectionChange(ByVal Target As Range)
' Check if the mouse Left button was pressed
If (isLeftMouseDown()) Then
... do some stuff on left click - for example ...
If (ActiveCell.Column = 1) Then
MsgBox "You LeftClick in column A"
End If
...
End If
End Sub
Caution :
The flag can be read for 1 second after the click event, they are then reseted. That is to prevent some side effect when leaving excel and coming back to it.
Addendum to the code answer:
As of VBA 7 and above, the 'Declare' statements at the beginning need to also include 'PtrSafe'. Microsft added this check to ensure that the 'Declare' statement is safe to run in 64-bit versions of Office. See the article here:
https://learn.microsoft.com/en-us/office/vba/language/concepts/getting-started/64-bit-visual-basic-for-applications-overview

Detecting Lost Focus in Excel Application, Workbook or Worksheet

Switching to another application via the system ALT-Tab hotkey, while working in MS Excel on MS-Windows causes Excel to lose the keyboard focus. How to detect this?
The Deactivate or WindowDeactivate events for the objects: Application or Workbook or Worksheet objects do not fire when MS Excel loses focus this way (of course, because losing the focus is not synonymous with Deactivating the window)
Try this code, please. I found it somewhere to the internet, three years ago and only adapted to serve my needs. For instance, it could not be stopped because of a wrong declaration of UnhookWinEvent API. Take care to not monitor the focus lost or got by using a MsgBox. In this way, pressing 'OK' the focus will be received again and you will be in an infinite loop. The focus status will be returned in the active sheet, range "A1" (received focus), respectively, "A2" (lost focus):
Copy the next code on top of a module (in the declarations area):
Option Explicit
Private Const EVENT_SYSTEM_FOREGROUND = &H3&
Private Const WINEVENT_OUTOFCONTEXT = 0
Private Declare PtrSafe Function SetWinEventHook Lib "user32.dll" (ByVal eventMin As Long, _
ByVal eventMax As Long, ByVal hmodWinEventProc As LongLong, ByVal pfnWinEventProc As LongLong, _
ByVal idProcess As Long, ByVal idThread As Long, ByVal dwFlags As Long) As Long
Private Declare PtrSafe Function GetCurrentProcessId Lib "kernel32" () As Long
Private Declare PtrSafe Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long
Private Declare PtrSafe Function UnhookWinEvent Lib "user32.dll" (ByVal hWinEventHook As Long) As Long
Private handlColl As Collection
Copy the next code inside the module:
Public Sub StartMonitoring() 'it can be called from a Workbook/Worksheet event
StartFocusMonitoring
End Sub
Public Function StartFocusMonitoring() As Long
If handlColl Is Nothing Then Set handlColl = New Collection
StartFocusMonitoring = SetWinEventHook(EVENT_SYSTEM_FOREGROUND, EVENT_SYSTEM_FOREGROUND, 0&, _
AddressOf WinEventFunc, 0, 0, WINEVENT_OUTOFCONTEXT)
handlColl.aDD StartFocusMonitoring
End Function
Public Sub StopEventHook(lHook As Long)
Dim LRet As Long
If lHook = 0 Then Exit Sub`
LRet = UnhookWinEvent(lHook)
End Sub
Public Sub StopMonitoring() 'it must be called manualy or by an event when need to stop monitoring...
'it did not work until I changed the StopEventHook declaration, using ByVal instead of ByRef
Dim vHook As Variant, lHook As Long
For Each vHook In handlColl
lHook = vHook
StopEventHook lHook
Next vHook
End Sub
Public Function WinEventFunc(ByVal HookHandle As Long, ByVal LEvent As Long, _
ByVal hWnd As Long, ByVal idObject As Long, ByVal idChild As Long, _
ByVal idEventThread As Long, ByVal dwmsEventTime As Long) As Long
'In case of an error the application will crush. So, bypassing the error is good to be done...`
On Error Resume Next
Dim thePID As Long`
If LEvent = EVENT_SYSTEM_FOREGROUND Then
GetWindowThreadProcessId hWnd, thePID
If thePID = GetCurrentProcessId Then
'Do not use here a MsgBox, because after pressing OK Excel application
'will receive focus and you will stay in an infinite loop...
Application.OnTime Now, "Event_GotFocus"
Else
Application.OnTime Now, "Event_LostFocus"
End If
End If
On Error GoTo 0
End Function
Public Sub Event_GotFocus()
Range("a1").value = "Received Focus"
Range("a2").value = ""
End Sub
Public Sub Event_LostFocus()
Range("a2").value = "Lost focus"
Range("a1").value = ""
End Sub
You must start monitoring from StartMonitoring Sub which can be called directly or through an event (Workbook_Open, for instance).
The monitoring can be stopped calling StopMonitoring Sub...

Log off windows using VBA

I'm making an application in VBA and after 15 or so minutes of inactivity, the program opens a seperate userform and starts counting down from 60. After that time has expired, I wish to make windows log off so that any data won't get compromised by students or nothing gets destroyed. However; after spending nearly an hour going through forums and my textbook, I can't find a functioning, simple piece of code. Any snippets or suggestions are welcome :)
Thank you very much :)
You could just lock the workstation
Declare Function LockWorkStation Lib "user32.dll" () As Long
Public Sub LockPC()
LockWorkStation
End Sub
Update You could also logoff but be aware all applications are closed and normally nothing will be saved.
Option Explicit
Private Declare Function ExitWindowsEx Lib "User32" ( _
ByVal uFlags As Long, _
dwReserved As Long) As Long
Private Const EWX_FORCE = 4
Private Const EWX_LOGOFF = 0
Private Const EWX_REBOOT = 2
Private Const EWX_SHUTDOWN = 1
Private Const EWX_POWEROFF = 8
Sub Logoff()
Dim Retval As Long
Retval = ExitWindowsEx(EWX_LOGOFF, 0&)
If Retval = 0 Then MsgBox "Could not log off", vbOKOnly + vbInformation, "Logoff"
End Sub
Attention For a 64-bit Excel you have to adapt the api declarations, have a look here. Often you only have to add PtrSafe and replace Long with LongLong
Update 2022/08/10 API calls for 64-bit Excel
Declare PtrSafe Function LockWorkStation Lib "user32.dll" () As Long
Declare PtrSafe Function ExitWindowsEx Lib "user32" _
(ByVal uFlags As Long, ByVal dwReserved As Long) As Long
You can also use the shutdown.exe to log off. Example below
Sub LogOffComputer()
'https://learn.microsoft.com/en-us/windows-server/administration/windows-commands/shutdown
Dim oShell
Set oShell = CreateObject("Shell.Application")
oShell.ShellExecute "cmd.exe", "shutdown.exe /l /f"
Set oShell = Nothing
End Sub
This works on my 64 bit Excel:
Sub shut()
Shell "Shutdown -s -t 20", vbHide
End Sub
Although I am looking for a method to close any running apps first, since I suppose it can make the system corrupt to close apps by shutdown windows with running apps.

Stop transaction in SAP with VBA

I have a working VBA macro which enters SAP, starts a transaction and then extracts the data in spreadsheet.
But sometimes the calculation runs too long, or I just would like to stop it to intervene. There is a functionality on the toolbar at the top left corner, where the user can "stop transaction" manually.
Is there any SAP script code for the "stop transaction" button, so I can avoid the manual step?
SAP toolbar:
It is assumed that the VBA macro is running in the first session. If a second session is opened before starting the macro, it can be used to close the first session.
for example:
Set SapGuiAuto = GetObject("SAPGUI")
Set SAPapp = SapGuiAuto.GetScriptingEngine
Set SAPconnection = SAPapp.Children(0)
Set session = SAPconnection.Children(1)
session.findById("wnd[0]/tbar[0]/okcd").text = "/i1"
session.findById("wnd[0]").sendVKey 0
session.createSession
Application.Wait (Now + TimeValue("0:00:05"))
session.findById("wnd[0]/tbar[0]/okcd").text = "/i3"
session.findById("wnd[0]").sendVKey 0
session.createSession
Application.Wait (Now + TimeValue("0:00:05"))
Whether a "rollback" is carried out or not, would be to test.
Regards,
ScriptMan
I guess you better record a script with this scenario, then you can re-use it any time.
Otherwise, I am at the very moment struggling with the same case, but with the run time counter part to leave the tcode if running too long.
It is a hart nut to crack too, but a different topic.
Update: realizing that there is no way to get the 'Stop Transaction' step recorded, I applied the above method - thank you Script Man, it was not the first time you saved the day.
For anyone reading this thread - may be useful to know how to split the SAP runtime from VBA script runtime.
I introduced an object that is the 'Execute' command itself. This way, SAP takes the command and starts execution, while the macro will step over as it is not an actual command but applying a new object only. This trick can help users to write a time counter and drop the session if running too long.
For reference, see my code here - I quoted the part of my code that contains the relevant method.
'check whether you already have an extra session open to close the long running session
'open one if needed
On Error Resume Next
Set session1 = Connection.Children(1)
If Err.Number <> 0 Then
session.CreateSession
Application.Wait (Now + TimeValue("0:00:05"))
're-set the sessions, ensuring you use the first session for actual work and keep session1 in background
Set session = Connection.Children(0)
Set session1 = Connection.Children(1)
SesCount = Connection.Sessions.Count()
Err.Clear
On Error GoTo 0
End If
'get the ID of first session, so you can enter the correct terminating transaction code when needed
sessionID = Mid(session.ID, (InStrRev(session.ID, "[") + 1), 1)
Terminator = "/i" & sessionID + 1
session.FindById("wnd[0]").Maximize
'some code comes here
'here I use an object to apply the execute button - this way parallel with the SAP runtime, the VBA script can proceed.
perec = session.FindById("wnd[0]/tbar[1]/btn[8]").press
'here we set a loop to check whether system is busy over a certain time then we may interrupt:
Do
Application.Wait (Now + TimeValue("0:00:05"))
SecondsElapsed = SecondsElapsed + 5
fityirc = session.Busy()
if fityirc = False then
exit Do
end if
Loop Until SecondsElapsed >= 100
If fityirc = True Then
session1.FindById("wnd[0]/tbar[0]/okcd").Text = Terminator
session1.FindById("wnd[0]").sendVKey 0
End If
'...and so on. This solution is applied in a loop to extract datasets massively without human interaction.
Or, have a look at code I've just written and tested to use the Windows API to run the Stop Transaction menu item. I raised a question about it on the SAP forum, but figured it out myself in the meantime (SAP Forum)
Private Declare PtrSafe Function FindWindowA Lib "user32.dll" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
Private Declare PtrSafe Function GetSystemMenu Lib "user32" (ByVal hWnd As LongPtr, ByVal bRevert As Long) As LongPtr
Private Declare PtrSafe Function GetMenuItemCount Lib "user32" (ByVal hMenu As LongPtr) As Long
Private Declare PtrSafe Function GetMenuItemInfoA Lib "user32" (ByVal hMenu As LongPtr, ByVal un As Long, ByVal b As Long, lpMenuItemInfo As MENUITEMINFO) As Long
Private Declare PtrSafe Function SendMessageA Lib "user32" (ByVal hWnd As LongPtr, ByVal wMsg As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr
Public Const MIIM_STRING As Integer = &H40
Public Const MIIM_ID = &H2
Public Const WM_COMMAND = &H111
Public Const WM_SYSCOMMAND = &H112
Public Type MENUITEMINFO
cbSize As Long
fMask As Long
fType As Long
fState As Long
wID As LongPtr
hSubMenu As Long
hbmpChecked As Long
hbmpUnchecked As Long
dwItemData As Long
dwTypeData As String
cch As Long
End Type
Public Function RunMenuItemByString(ByVal sMenuItem As String, _
ByVal sWindowClass As String, _
ByVal sWindowText As String, _
ByVal iCommandType As Integer) As Boolean
Dim hWnd As LongPtr, hMenu As LongPtr, lpMenuItemID As LongPtr
Dim lngMenuItemCount As Long, lngMenuItem As Long, lngResultMenuItemInfo As Long
Dim typMI As MENUITEMINFO
Dim s As String
Dim blnRet As Boolean
hWnd = FindWindowA(sWindowClass, sWindowText)
hMenu = GetSystemMenu(hWnd, 0&)
lngMenuItemCount = GetMenuItemCount(hMenu)
For lngMenuItem = 0 To lngMenuItemCount - 1
typMI.cbSize = Len(typMI)
typMI.dwTypeData = String$(255, " ")
typMI.cch = Len(typMI.dwTypeData)
typMI.fMask = MIIM_STRING Or MIIM_ID
lngResultMenuItemInfo = GetMenuItemInfoA(hMenu, lngMenuItem, 1, typMI)
s = Trim$(typMI.dwTypeData)
lpMenuItemID = typMI.wID
If InStr(1, s, sMenuItem, vbTextCompare) > 0 Then
blnRet = SendMessageA(hWnd, iCommandType, lpMenuItemID, 0&) = 0
Exit For
End If
Next lngMenuItem
RunMenuItemByString = blnRet
End Function
Public Function TestRunMenuItemByString()
lpHwndSAPSession = oSAPSession.FindById("wnd[0]").Handle
sWindowText = GetWindowText(lpHwndSAPSession)
TestRunMenuItemByString = RunMenuItemByString("Stop Transaction", "SAP_FRONTEND_SESSION", sWindowText, WM_SYSCOMMAND)
End Function
The TestRunMenuItemByString function can be used only after a session is started, and will only work if there is actually a transaction executing. You will need to figure out how to reference your sap session object (oSAPSession) in order to use the Handle value from it.
The declarations should work in both 32 bit and 64 bit versions of VBA and the LongPtr has been used for the handle (h) and pointer (lp) variables to reflect this.
This was tested in Microsoft Access, but I see no reason why it shouldn't work in VBA in other Office applications. I can't vouch for it being adaptable for VBScript.

VBA automation of Excel leaves a process in memory after Quit

I have seen a lot of suggestions for this problem, and I have tried them all, but none seem to work. The VBA code is in a non-Microsoft product (SAP Business Objects, which might be the problem). I create an Excel object:
Set oExcel = CreateObject("Excel.Application")
Load the contents from column 1 of one of the WorkSheets in a particular workbook, then close Excel. Each time, it leaves a process in memory, taking up 5+ mb of memory.
I tried making the oExcel object visible, so that at least I could kill it without resorting to the Task Manager, but when I call Quit, the UI quits, and still leaves the process.
Every time I run the code, it creates a new process. So I tried to reuse any existing Excel processes by calling
Set m_oExcel = GetObject(, "Excel.Application")
and only creating it if that call returns nothing,
That did not proliferate the processes, but the single process grew by 5+ mb each time, so essentially the same problem.
In each case, I close the workbook I opened and set DisplayAlerts to False before quitting:
m_oBook.Close SaveChanges:=False
m_oExcel.DisplayAlerts = False
m_oExcel.Quit
This bit of code has been in use for at least five years, but this problem did not crop up until we moved to Windows 7.
Here is the full code in case it helps. Note all the Excel objects are module level variables ("m_" prefix) per one suggestion, and I have used the "one-dot" rule per another suggestion. I also tried using generic objects (i.e. late bound) but that did not resolve the problem either:
Private Function GetVariablesFromXLS(ByVal sFile As String) As Boolean
On Error GoTo SubError
If Dir(sFile) = "" Then
MsgBox "File '" & sFile & "' does not exist. " & _
"The Agent and Account lists have not been updated."
Else
Set m_oExcel = CreateObject("Excel.Application")
Set m_oBooks = m_oExcel.Workbooks
Set m_oBook = m_oBooks.Open(sFile)
ThisDocument.Variables("Agent(s)").Value = DelimitedList("Agents")
ThisDocument.Variables("Account(s)").Value = DelimitedList("Accounts")
End If
GetVariablesFromXLS = True
SubExit:
On Error GoTo ResumeNext
m_oBook.Close SaveChanges:=False
Set m_oBook = Nothing
Set m_oBooks = Nothing
m_oExcel.DisplayAlerts = False
m_oExcel.Quit
Set m_oExcel = Nothing
Exit Function
SubError:
MsgBox Err.Description
GetVariablesFromXLS = False
Resume SubExit
ResumeNext:
MsgBox Err.Description
GetVariablesFromXLS = False
Resume Next
End Function
Most times this happens because Excel is keeping a COM Add-in open. Try using the link below for help on removing the COM Add-in.
Add or remove add-ins
I find particular comfort in the note:
Note This removes the add-in from memory but keeps its name in the list of available add-ins. It does not delete the add-in from your computer.
Adding an answer based on David Zemens comment. Works for me.
m_oExcel.Quit '<- Still in Task Manager after this line
Set m_oExcel = Nothing '<- Gone after this line
This question has already been answered by Acantud in response to a subsequent post:
https://stackoverflow.com/questions/25147242
Fully qualify your references to objects within the Excel workbook you open to avoid creating orphaned processes in the task manager. In this case, the solution is to prefix DelimitedList with m_oBook, such as
ThisDocument.Variables("Agent(s)").Value = m_oBook.DelimitedList("Agents")
Though this isn't supposed to happen, you could send excel a "WindowClose" message in order to force close.
You'll be needing these API functions
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, ByVal uExitCode As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hWnd As Long, lpdwProcessId As Long) As Long
Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
And it should look something like this:
// First, get the handle
hWindow = FindWindow(vbNullString, "Excel")
//Get proccess ID
GetWindowThreadProcessId(hWindow, ProcessValueID)
//Kill the process
ProcessValue = OpenProcess(PROCESS_ALL_ACCESS, CLng(0), ProcessValueID)
TerminateProcess(ProcessValue, CLng(0))
CloseHandle ProcessValueID
Need to use only:
Private Sub Workbook_BeforeClose(Cancel As Boolean)
Excel.Application.Quit
End Sub

Resources