PDA

View Full Version : [SOLVED:] Close All Instances Of Excel Without Saving Any Changes



HTSCF Fareha
06-14-2021, 12:00 PM
I understand that this might seem a bit of an unusual one to request, but I would really appreciate some help in trying to achieve this.

I have the following so far, which doesn't quite close everything. The workbook that holds the sub exits and closes, but other workbooks that have been used, that have the default Book1, Book2, Book3 etc. and still contain data that have not been saved, still remain open.


Private Sub cmdExit_Click()

For Each wb In Workbooks
If wb.Name <> ThisWorkbook.Name Then
wb.Close SaveChanges:=False
End If
Next

For Each wb In Workbooks
If Not wb.FullName = ThisWorkbook.FullName Then wb.Close False
Next

ThisWorkbook.Saved = True
Application.Quit

End Sub

Many thanks!
Steve

Paul_Hossler
06-14-2021, 12:08 PM
Nit Pick --


Close All Instances Of Excel Without Saving Any Changes

You're really not closing all instances.

You're closing all open workbooks





Option Explicit


Sub cmdExit_Click()
Dim wb As Workbook


For Each wb In Workbooks
If Not wb Is ThisWorkbook Then wb.Close SaveChanges:=False
Next

ThisWorkbook.Saved = True
Application.Quit

End Sub

HTSCF Fareha
06-14-2021, 12:39 PM
Nit Pick --


You're really not closing all instances.

You're closing all open workbooks



Many thanks, Paul and point well made. :yes

Steve

snb
06-15-2021, 07:06 AM
Sub M_snb()
workbooks.close
End Sub

Paul_Hossler
06-15-2021, 07:16 AM
Sub M_snb()
workbooks.close
End Sub

Prompts for unsaved WBs

Doesn't close Excel

snb
06-15-2021, 07:48 AM
Sub M_snb()
Application.displayalerts=false
Application.quit
End Sub

HTSCF Fareha
06-15-2021, 09:17 AM
Thanks to you both for the further updates.

I was going to have to open the thread again with Paul's suggestion, as this didn't want to close the other separate instances of Excel with their respective (unsaved) Book1, Book2, Book3 etc.

I'm not sure if this would make a difference if the other workbooks were in separate instances of Excel, which is the scenario that I have?

Anyhow, I'm going to have to wait until tomorrow to try SNBs post at #6 when I'm back in the office. Fingers crossed that it closes all instances of Excel without saving anything.

Thanks!
Steve

HTSCF Fareha
06-16-2021, 11:13 AM
Well I used snb's code today and to my surprise, it still didn't have the desired effect.

It closed the Workbook that had the sub in it, but the other workbooks stayed open and as they were. :banghead:

Any other ideas?

Paul_Hossler
06-16-2021, 01:46 PM
Any other ideas?

Did the code in post #2 work?

Artik
06-16-2021, 07:52 PM
It is possible that some workbooks are open in other instances of the application. Then you will have to search for these instances. But this OP has to investigate.
All of the above codes close workbooks from only one instance.

Artik

Paul_Hossler
06-16-2021, 09:57 PM
IIRC only Excel 2013 allowed multiple instances of Excel (i.e. 2+ enteries in Task Manager) so I'd guess that there's still something else going on

https://docs.microsoft.com/en-us/office/vba/excel/concepts/programming-for-the-single-document-interface-in-excel

This closes all visible and hidden workbooks in the instance and is only a slight tweak of the original macro


Option Explicit

Sub cmdExit_Click()
Dim wb As Workbook

For Each wb In Workbooks
If Not wb Is ThisWorkbook Then wb.Close SaveChanges:=False
Next

ThisWorkbook.Saved = True
Application.Quit

End Sub

HTSCF Fareha
06-16-2021, 10:08 PM
Paul, in answer to your question in #9, your code produced the same result as the other suggested solutions.

I think that Artik has probably hit the nail on the head in that our bespoke programme is using the option to "Export date to Excel" which is producing the Book1, Book2, Book3 etc.

With my obviously limited knowledge of Excel, I hadn't thought of this, but now it has been mentioned by Artik then this seems that this is the logical reason why.

I'm guessing that this changes things somewhat? Sorry!

Steve

HTSCF Fareha
06-16-2021, 10:10 PM
Must have been typing at the same time Paul.

I will give your suggestion a go today and get back to you later.

Many thanks!

Steve

[Edit]
I've just read the link that you provided and this is exactly what is happening. I think work is using Office 2016, so this supports the "creation of multiple SDI".

snb
06-17-2021, 01:00 AM
This can only be run in Word.
The question to save changed files can't be hidden and has to be answered by the user.


Sub M_snb()
For Each it In Tasks
If InStr(it.Name, ".xls") Then
it.Activate
it.Close
End If
Next
End Sub

HTSCF Fareha
06-17-2021, 02:10 AM
Okay, so Paul's suggestion didn't work.

In relation to yours snb, would this need to be combined with other code to actually close everything, or will it run as is?

snb
06-17-2021, 03:19 AM
Please check it, starting the macro in Word.

HTSCF Fareha
06-17-2021, 05:48 AM
Okay, have run this from word. It gave a prompt for the first Workbook and closed it, but did nothing after that with the others that were still open. I thought it might be the file extension, so tried adjusting that to. xlsx, but still no go

(Edit) The only file for which the prompt was asked for was the .xlsm one.

Paul_Hossler
06-17-2021, 09:15 AM
1. I can't test this since I don't have a multi-instance capability

2. In a single instance, with multiple workbooks open it seems to work

3. I modified the StackOverflow code a bit, so you can blame me if it doesn't work

4. Good luck

edit - miscopied code in original post



Option Explicit


'https://stackoverflow.com/questions/2971473/can-vba-reach-across-instances-of-excel


Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As LongPtr) As LongPtr
Private Declare PtrSafe Function IIDFromString Lib "ole32" (ByVal lpsz As LongPtr, ByRef lpiid As UUID) As LongPtr
Private Declare PtrSafe Function AccessibleObjectFromWindow Lib "oleacc" (ByVal Hwnd As LongPtr, ByVal dwId As LongPtr, ByRef riid As UUID, ByRef ppvObject As Object) As LongPtr


Type UUID 'GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type


Const IID_IDispatch As String = "{00020400-0000-0000-C000-000000000046}"
Const OBJID_NATIVEOM As LongPtr = &HFFFFFFF0


' Run as entry point of example
Sub CloseAllWorkbooksWithoutSaving()
Dim i As Long
Dim xlApps() As Application
Dim wb As Workbook
Dim hRunningApp As LongPtr


hRunningApp = Application.HinstancePtr


If GetAllExcelInstances(xlApps) Then
For i = LBound(xlApps) To UBound(xlApps)
With xlApps(i)
If .HinstancePtr <> hRunningApp Then
For Each wb In .Workbooks
wb.Close SaveChanges:=False
Next

.ActiveWorkbook.Saved = True
.Quit
End If
End With
Next
End If


For Each wb In Application.Workbooks
If Not wb Is ThisWorkbook Then wb.Close SaveChanges:=False
Next


Application.ActiveWorkbook.Saved = True
Application.Quit
End Sub


' Actual public facing function to be called in other code
Public Function GetAllExcelInstances(xlApps() As Application) As Long
Dim n As Long
Dim app As Application
Dim hWndMain As LongPtr


On Error GoTo MyErrorHandler


' Cater for 100 potential Excel instances, clearly could be better
ReDim xlApps(1 To 100)


hWndMain = FindWindowEx(0&, 0&, "XLMAIN", vbNullString)


Do While hWndMain <> 0
Set app = GetExcelObjectFromHwnd(hWndMain)
If Not (app Is Nothing) Then
If n = 0 Then
n = n + 1
Set xlApps(n) = app
ElseIf checkHwnds(xlApps, app.Hwnd) Then
n = n + 1
Set xlApps(n) = app
End If
End If
hWndMain = FindWindowEx(0&, hWndMain, "XLMAIN", vbNullString)
Loop


If n Then
ReDim Preserve xlApps(1 To n)
GetAllExcelInstances = n
Else
Erase xlApps
End If


Exit Function


MyErrorHandler:
MsgBox "GetAllExcelInstances" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description


End Function


Private Function checkHwnds(xlApps() As Application, Hwnd As LongPtr) As Boolean
Dim i As Integer


For i = LBound(xlApps) To UBound(xlApps)
If xlApps(i).Hwnd = Hwnd Then
checkHwnds = False
Exit Function
End If
Next i


checkHwnds = True


End Function


Private Function GetExcelObjectFromHwnd(ByVal hWndMain As LongPtr) As Application
Dim hWndDesk As LongPtr
Dim Hwnd As LongPtr
Dim strText As String
Dim lngRet As Long
Dim iid As UUID
Dim obj As Object




On Error GoTo MyErrorHandler


hWndDesk = FindWindowEx(hWndMain, 0&, "XLDESK", vbNullString)


If hWndDesk <> 0 Then


Hwnd = FindWindowEx(hWndDesk, 0, vbNullString, vbNullString)


Do While Hwnd <> 0


strText = String$(100, Chr$(0))
lngRet = CLng(GetClassName(Hwnd, strText, 100))


If Left$(strText, lngRet) = "EXCEL7" Then


Call IIDFromString(StrPtr(IID_IDispatch), iid)


If AccessibleObjectFromWindow(Hwnd, OBJID_NATIVEOM, iid, obj) = 0 Then 'S_OK


Set GetExcelObjectFromHwnd = obj.Application
Exit Function


End If


End If


Hwnd = FindWindowEx(hWndDesk, Hwnd, vbNullString, vbNullString)
Loop


On Error Resume Next


End If


Exit Function


MyErrorHandler:
MsgBox "GetExcelObjectFromHwnd" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description


End Function

HTSCF Fareha
06-17-2021, 11:57 AM
Very many thanks, Paul for coming up with this.

I'm going to sign back into work just to see if this works as I'm itching to try it.

As with all sensible businesses, all the macro enabled templates that are used have to be digitally signed for approval and use. I want to put this code into my existing signed project, but was wondering exactly where one puts the following part

'https://stackoverflow.com/questions/2971473/can-vba-reach-across-instances-of-excel
Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As LongPtr) As LongPtr
Private Declare PtrSafe Function IIDFromString Lib "ole32" (ByVal lpsz As LongPtr, ByRef lpiid As UUID) As LongPtr
Private Declare PtrSafe Function AccessibleObjectFromWindow Lib "oleacc" (ByVal Hwnd As LongPtr, ByVal dwId As LongPtr, ByRef riid As UUID, ByRef ppvObject As Object) As LongPtr

Type UUID 'GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type

Const IID_IDispatch As String = "{00020400-0000-0000-C000-000000000046}"
Const OBJID_NATIVEOM As LongPtr = &HFFFFFFF0

If I place it directly at the top under 'Option Explicit' and then run it, I get a Compile error: Cannot define a Public user-defined type within an object module' on this line


Type UUID

HTSCF Fareha
06-17-2021, 01:28 PM
Okay, I solved my previous issue by placing everything except the below into a module.


' Run as entry point of example
Sub CloseAllWorkbooksWithoutSaving()
Dim i As Long
Dim xlApps() As Application
Dim wb As Workbook
Dim hRunningApp As LongPtr


hRunningApp = Application.HinstancePtr


If GetAllExcelInstances(xlApps) Then
For i = LBound(xlApps) To UBound(xlApps)
With xlApps(i)
If .HinstancePtr <> hRunningApp Then
For Each wb In .Workbooks
wb.Close SaveChanges:=False
Next

.ActiveWorkbook.Saved = True
.Quit
End If
End With
Next
End If


For Each wb In Application.Workbooks
If Not wb Is ThisWorkbook Then wb.Close SaveChanges:=False
Next


Application.ActiveWorkbook.Saved = True
Application.Quit
End Sub

Running it after signing back into work, after producing 6 workbooks, which are all unsaved and are as Book1, Book2, Book3 etc. I get the following error message as per the attached.

Paul_Hossler
06-17-2021, 01:57 PM
I want to put this code into my existing signed project, but was wondering exactly where one puts the following part

Explain that little (or a lot) more

Everything in my little test was in a single standard module, the Declares, the Type UUID, macros, etc.




Okay, I solved my previous issue by placing everything except the below into a module.

What happens if you put that in the module? I had everything in just one module


In that sub there are no 'With' satements, so I'm guessing that an object is not getting Set. The only objects are the xlApps() array

All I can suggest is

1. Put a break point on the line and then Add Watch to investigate xlApps

Also

2. Single step through the code to see if



If n = 0 Then
n = n + 1
Set xlApps(n) = app
ElseIf checkHwnds(xlApps, app.Hwnd) Then
n = n + 1
Set xlApps(n) = app
End If


is not setting the xlApps(n) entry

Again the Watch should show how many instances are being found

This is mine with only one instance (different system)

28616

Artik
06-17-2021, 04:20 PM
I tested the code shown by Paul. I had 4 Excel instances open, including one hidden.
The big surprise for me was this piece of code:
With xlApps(i)
If .HinstancePtr <> hRunningApp Then
...
Assuming that the xlApps variable contains several different instances, the above condition never meets, because for all xlApps (i) .HinstancePtr = hRunningApp.
I looked at the help and Bill wrote in it:
Application.Hinstance property (Excel)
Returns a handle to the instance of Excel represented by the Application object. Since these are different instances, we should get different handles.:bug:
That's why I used a different handle - Application.hwnd.


Corrected code that works for me:
Option Explicit

'https://stackoverflow.com/questions/2971473/can-vba-reach-across-instances-of-excel
'http://www.vbaexpress.com/forum/showthread.php?68893-Close-All-Instances-Of-Excel-Without-Saving-Any-Changes

Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As LongPtr) As LongPtr
Private Declare PtrSafe Function IIDFromString Lib "ole32" (ByVal lpsz As LongPtr, ByRef lpiid As UUID) As LongPtr
Private Declare PtrSafe Function AccessibleObjectFromWindow Lib "oleacc" (ByVal Hwnd As LongPtr, ByVal dwId As LongPtr, ByRef riid As UUID, ByRef ppvObject As Object) As LongPtr


Type UUID 'GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type


Const IID_IDispatch As String = "{00020400-0000-0000-C000-000000000046}"
Const OBJID_NATIVEOM As LongPtr = &HFFFFFFF0


' Run as entry point of example
Sub CloseAllWorkbooksWithoutSaving()
Dim i As Long
Dim xlApps() As Application
Dim hRunningApp As LongPtr '<--to remove

hRunningApp = Application.HinstancePtr '<--to remove


If GetAllExcelInstances(xlApps) Then
Debug.Print String(30, "-")

For i = LBound(xlApps) To UBound(xlApps)
With xlApps(i)
'============= For test only ==============
Debug.Print "Hinstance: " & .HinstancePtr & " | hRunApp:" & hRunningApp 'Application.HinstancePtr
Debug.Print "Found instance.Hwnd: " & .Hwnd & " | This instance.Hwnd: " & Application.Hwnd
Debug.Print "WrkBks.Count: " & .Workbooks.Count
Debug.Print .Caption
Debug.Print "Is visible: " & .Visible
Debug.Print String(30, "-")
'==========================================

If .Hwnd <> Application.Hwnd Then
.DisplayAlerts = False
.Quit
End If
End With
Next i

Debug.Print String(30, "=")
End If


Application.DisplayAlerts = False
Application.Quit
End Sub



' Actual public facing function to be called in other code
Public Function GetAllExcelInstances(xlApps() As Application) As Long
Dim n As Long
Dim app As Application
Dim hWndMain As LongPtr

On Error GoTo MyErrorHandler

' Cater for 100 potential Excel instances, clearly could be better
ReDim xlApps(1 To 100)

hWndMain = FindWindowEx(0&, 0&, "XLMAIN", vbNullString)


Do While hWndMain <> 0
Set app = GetExcelObjectFromHwnd(hWndMain)

If Not (app Is Nothing) Then
'If n = 0 Then
n = n + 1
Set xlApps(n) = app
'ElseIf checkHwnds(xlApps, app.Hwnd) Then
'n = n + 1
'Set xlApps(n) = app
'End If
End If

hWndMain = FindWindowEx(0&, hWndMain, "XLMAIN", vbNullString)

Loop


If n Then
ReDim Preserve xlApps(1 To n)
GetAllExcelInstances = n
Else
Erase xlApps
End If

Exit Function

MyErrorHandler:
MsgBox "GetAllExcelInstances" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description
End Function


Private Function GetExcelObjectFromHwnd(ByVal hWndMain As LongPtr) As Application
Dim hWndDesk As LongPtr
Dim Hwnd As LongPtr
Dim strText As String
Dim lngRet As Long
Dim iID As UUID
Dim obj As Object

On Error GoTo MyErrorHandler

hWndDesk = FindWindowEx(hWndMain, 0&, "XLDESK", vbNullString)

If hWndDesk <> 0 Then

Hwnd = FindWindowEx(hWndDesk, 0, vbNullString, vbNullString)

Do While Hwnd <> 0

strText = String$(100, Chr$(0))
lngRet = CLng(GetClassName(Hwnd, strText, 100))

If Left$(strText, lngRet) = "EXCEL7" Then

Call IIDFromString(StrPtr(IID_IDispatch), iID)

If AccessibleObjectFromWindow(Hwnd, OBJID_NATIVEOM, iID, obj) = 0 Then 'S_OK
Set GetExcelObjectFromHwnd = obj.Application
Exit Function
End If

End If

Hwnd = FindWindowEx(hWndDesk, Hwnd, vbNullString, vbNullString)
Loop

On Error Resume Next

End If

Exit Function

MyErrorHandler:
MsgBox "GetExcelObjectFromHwnd" & vbCrLf & vbCrLf & "Err = " & Err.Number & vbCrLf & "Description: " & Err.Description
End Function

Artik

Paul_Hossler
06-17-2021, 05:36 PM
Thanks!!!

I'm using Office 365 and I couldn't get multiple Excel instances to open so I could test

I think that the code I 'borrowed' could be tightened up a bit, but since I couldn't see any way to test, I tried to leave things alone

HTSCF Fareha
06-18-2021, 01:16 AM
Many thanks to you both!

The stuff that you are mentioning is way over my head I'm afraid to say. :bow:

I signed back in to work and made the modifications as suggested and can say it works brilliantly!!

I'm one very happy chap that doesn't have to systematically go through every workbook instance and click the prompt before closing. :biggrin:

Thank you!!

For anyone else using this code it should come with a massive word of warning as it will obviously exit Excel completely without saving anything.

Regards
Steve

Artik
06-18-2021, 01:30 AM
I'm using Office 365 and I couldn't get multiple Excel instances to open so I could test
Paul, but that doesn't excuse you :winking2:
I think you forgot the code
Sub NewExcelInstance()
Dim xlApp As Excel.Application

Set xlApp = New Excel.Application
xlApp.Workbooks.Add
xlApp.Visible = True

End Sub
Artik

Paul_Hossler
06-18-2021, 07:04 AM
:doh:

Didn't think about creating them programmaically

Jan Karel Pieterse
06-18-2021, 08:16 AM
Paul: Immediately after launching Excel, press and hold the alt key.

Steve: If it does not have to be VBA and all you want is shut down all Excel windows belonging to one Excel.exe without saving, simply Shift+click the close box in the top-right corner. Then when the first save prompt comes, hold shift and click No.

HTSCF Fareha
06-18-2021, 09:48 AM
It does have to be VBA Jan, as lots of other things are happening with data being pulled from these Workbooks. The scenario that it is being used in it is safer so as to not confuse data.