PDA

View Full Version : Solved: Launch Excel Without CreateObject



geekgirlau
11-15-2009, 04:28 PM
Hi all,

I have a fairly simple requirement to launch Excel from Access. The procedure creates a new document based on a template (depending on the report selected by the user) and in many cases runs additional code after updating data.

The issue is with the setup of MS Office:

The organisation is in the process of standardising on Office 2007, but currently there are versions 2003 and 2000 still in use. As a result, I'm using late binding.
GetObject works without a hitch, so if the user already has Excel running I don't have an issue.
CreateObject launches a 2007 Microsoft Office system Setup screen, starts to launch Excel, then crashes. To date I have been unable to get information from the service desk regarding the setup, however I do know that there's some virtualisation going on.
I have no control over the configuration of Office internally.This is a scaled-down version of the current code, which is pretty standard (ignore the lack of error handling - the real one does have some, promise!):

Sub LaunchExcel()
Dim objXL As Object

' use existing Excel session if open
On Error Resume Next
Set objXL = GetObject(, "Excel.Application")

If Err.Number <> 0 Then
Set objXL = CreateObject("Excel.Application")
End If

On Error GoTo 0
With objXL
' … blah blah
End With

Set objXL = Nothing
End Sub

As CreateObject doesn't work and the path for MS Office applications does not appear in the environment variables, I'm hoping someone can suggest an alternative method of launching any version of Excel if it is not already open. Currently I've setup my code so that if GetObject fails, the user receives a message asking them to launch Excel and try again. Not the most brilliant solution :confused3 .

CreganTur
11-17-2009, 10:45 AM
I use the following code to open Excel files. If you can determine up front whether you need 2003 or 2007, you can use a different filepath to the excel.exe and call the appropriate one. If not, then use OFFICE11 as a default and have error trapping that changes the filepath to 2007's filepath and attempts that.

Sub OpenReport(FileName As String)
Call Shell("C:\Program Files\Microsoft Office\OFFICE11\excel.exe " & Chr(34) _
& FileName, 1)
End Sub

HTH:thumb

geekgirlau
11-17-2009, 03:59 PM
The path to Excel.EXE is problematic - v2007 will be standard, but earlier versions are not. ASAIK Shell only works with EXE files - do you know of a way I can launch the template without specifying the program?

Tommy
11-19-2009, 10:51 AM
FWIW

The regestry has HKEY_CLASSES_ROOT\Applications\EXCEL.EXE\shell\New\command\default

which gives you the path to the excel exe.

geekgirlau
11-19-2009, 06:16 PM
Nope, this fails as well. The path is correctly identified, and it looks like Shell starts to load Excel but it then displays the Office System Setup again and Excel crashes.


Option Compare Database
Option Explicit
'********Code Start**************
'This code was originally written by Terry Kreft
' and Dev Ashish.
'It is not to be altered or distributed,
'except as part of an application.
'You are free to use it in any application,
'provided the copyright notice is left unchanged.
'
'Code Courtesy of
'Dev Ashish & Terry Kreft
'
Public Const HKEY_CLASSES_ROOT = &H80000000
Public Const HKEY_CURRENT_USER = &H80000001
Public Const HKEY_LOCAL_MACHINE = &H80000002
Public Const HKEY_USERS = &H80000003
Public Const HKEY_PERFORMANCE_DATA = &H80000004
Public Const HKEY_CURRENT_CONFIG = &H80000005
Public Const HKEY_DYN_DATA = &H80000006
Private Const STANDARD_RIGHTS_READ = &H20000
Private Const KEY_QUERY_VALUE = &H1&
Private Const KEY_ENUMERATE_SUB_KEYS = &H8&
Private Const KEY_NOTIFY = &H10&
Private Const SYNCHRONIZE = &H100000
Private Const KEY_READ = ((STANDARD_RIGHTS_READ Or _
KEY_QUERY_VALUE Or _
KEY_ENUMERATE_SUB_KEYS Or _
KEY_NOTIFY) And _
(Not SYNCHRONIZE))
Private Const MAXLEN = 256
Private Const ERROR_SUCCESS = &H0&
Const REG_NONE = 0
Const REG_SZ = 1
Const REG_EXPAND_SZ = 2
Const REG_BINARY = 3
Const REG_DWORD = 4
Const REG_DWORD_LITTLE_ENDIAN = 4
Const REG_DWORD_BIG_ENDIAN = 5
Const REG_LINK = 6
Const REG_MULTI_SZ = 7
Const REG_RESOURCE_LIST = 8
Type FILETIME
dwLowDateTime As Long
dwHighDateTime As Long
End Type
Private Declare Function apiRegOpenKeyEx Lib "advapi32.dll" _
Alias "RegOpenKeyExA" (ByVal hKey As Long, _
ByVal lpSubKey As String, ByVal ulOptions As Long, _
ByVal samDesired As Long, ByRef phkResult As Long) _
As Long
Private Declare Function apiRegCloseKey Lib "advapi32.dll" _
Alias "RegCloseKey" (ByVal hKey As Long) As Long
Private Declare Function apiRegQueryValueEx Lib "advapi32.dll" _
Alias "RegQueryValueExA" (ByVal hKey As Long, _
ByVal lpValueName As String, ByVal lpReserved As Long, _
ByRef lpType As Long, lpData As Any, _
ByRef lpcbData As Long) As Long
Private Declare Function apiRegQueryInfoKey Lib "advapi32.dll" _
Alias "RegQueryInfoKeyA" (ByVal hKey As Long, _
ByVal lpClass As String, ByRef lpcbClass As Long, _
ByVal lpReserved As Long, ByRef lpcSubKeys As Long, _
ByRef lpcbMaxSubKeyLen As Long, _
ByRef lpcbMaxClassLen As Long, _
ByRef lpcValues As Long, _
ByRef lpcbMaxValueNameLen As Long, _
ByRef lpcbMaxValueLen As Long, _
ByRef lpcbSecurityDescriptor As Long, _
ByRef lpftLastWriteTime As FILETIME) As Long
Function fReturnRegKeyValue(ByVal lngKeyToGet As Long, _
ByVal strKeyName As String, _
ByVal strValueName As String) _
As String
Dim lnghKey As Long
Dim strClassName As String
Dim lngClassLen As Long
Dim lngReserved As Long
Dim lngSubKeys As Long
Dim lngMaxSubKeyLen As Long
Dim lngMaxClassLen As Long
Dim lngValues As Long
Dim lngMaxValueNameLen As Long
Dim lngMaxValueLen As Long
Dim lngSecurity As Long
Dim ftLastWrite As FILETIME
Dim lngType As Long
Dim lngData As Long
Dim lngTmp As Long
Dim strRet As String
Dim varRet As Variant
Dim lngRet As Long

On Error GoTo fReturnRegKeyValue_Err

'Open the key first
lngTmp = apiRegOpenKeyEx(lngKeyToGet, _
strKeyName, 0&, KEY_READ, lnghKey)
'Are we ok?
If Not (lngTmp = ERROR_SUCCESS) Then Err.Raise _
lngTmp + vbObjectError
lngReserved = 0&
strClassName = String$(MAXLEN, 0): lngClassLen = MAXLEN
'Get boundary values
lngTmp = apiRegQueryInfoKey(lnghKey, strClassName, _
lngClassLen, lngReserved, lngSubKeys, lngMaxSubKeyLen, _
lngMaxClassLen, lngValues, lngMaxValueNameLen, _
lngMaxValueLen, lngSecurity, ftLastWrite)
'How we doin?
If Not (lngTmp = ERROR_SUCCESS) Then Err.Raise _
lngTmp + vbObjectError

'Now grab the value for the key
strRet = String$(MAXLEN - 1, 0)
lngTmp = apiRegQueryValueEx(lnghKey, strValueName, _
lngReserved, lngType, ByVal strRet, lngData)
Select Case lngType
Case REG_SZ
lngTmp = apiRegQueryValueEx(lnghKey, strValueName, _
lngReserved, lngType, ByVal strRet, lngData)
varRet = Left(strRet, lngData - 1)
Case REG_DWORD
lngTmp = apiRegQueryValueEx(lnghKey, strValueName, _
lngReserved, lngType, lngRet, lngData)
varRet = lngRet
Case REG_BINARY
lngTmp = apiRegQueryValueEx(lnghKey, strValueName, _
lngReserved, lngType, ByVal strRet, lngData)
varRet = Left(strRet, lngData)
End Select

'All quiet on the western front?
If Not (lngTmp = ERROR_SUCCESS) Then Err.Raise _
lngTmp + vbObjectError
fReturnRegKeyValue_Exit:
fReturnRegKeyValue = varRet
lngTmp = apiRegCloseKey(lnghKey)
Exit Function
fReturnRegKeyValue_Err:
varRet = "Error: Key or Value Not Found."
Resume fReturnRegKeyValue_Exit
End Function
Function fGetExcelPath() As String
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ~~~~~~~~~~~~~~
' Purpose: Capture the path for EXCEL.EXE
'
' Limitations: Normally if GetObject fails you would use CreateObject to create a new
' instance of Excel. However this launches an Office installer screen that
' then generates an error. Therefore have had to capture a registry setting
' in order to launch Excel.
'~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ~~~~~~~~~~~~~~
Dim strPath As String


strPath = fReturnRegKeyValue(HKEY_CLASSES_ROOT, "Applications\EXCEL.EXE\shell\New\command", "")
If InStr(1, strPath, "/") > 0 Then
strPath = Trim(Left(strPath, InStr(1, strPath, "/") - 1))
End If

fGetExcelPath = strPath
End Function

Sub LaunchExcel()
Dim objXL As Object
Dim strPathXL As String
Dim blnAttempted As Boolean
Dim x

XLReport:
On Error Resume Next
Set objXL = GetObject(, "Excel.Application")
If Err.Number <> 0 Then
' normal process to use - fails
' Set objXL = CreateObject("Excel.Application")

If blnAttempted = False Then
strPathXL = fGetExcelPath()

MsgBox "Excel is not currently running. Attempting to launch Excel from:" & vbCrLf & vbCrLf & _
strPathXL, vbInformation

Err.Clear
blnAttempted = True

x = Shell(strPathXL, vbNormalFocus)

If x = 0 Then
MsgBox "Launch Failed", vbCritical
Else
GoTo XLReport
End If

Else
MsgBox "Attempt to launch Excel has FAILED", vbCritical
End If
Else
MsgBox "Successfully connected to Excel"
End If

ExitHere:
On Error Resume Next
Set objXL = Nothing
Exit Sub

ErrHandler:
MsgBox "(" & Err.Number & ")" & vbCrLf & Err.Description, vbCritical, "Unexpected Error"
Resume ExitHere
End Sub

Bob Phillips
11-28-2009, 03:06 AM
I would have thought that the problem is nt in CreateObject or in Shell per se, and it doubt it would be any less of a problem using early binding. The problem must be in what the virtualisation is doing.

I would try instancing Excel using early binding, and whatever the results, throw the problem back at your IT, it has to be a setup issue.

geekgirlau
11-30-2009, 03:21 PM
Given the overall lack of interest shown by our external support provider, I won't hold my breath on this one!

Bob Phillips
12-01-2009, 06:09 AM
gga, can't you get you boss to rattle a few cages for you? If it is useful work, that is eactly what bosses are for.

geekgirlau
12-01-2009, 03:50 PM
I'm a contractor on a project that is winding down in 30 days ... :100:

stanl
12-02-2009, 03:44 AM
You said GetObject() works. Then it should work at the file/template level even if Excel is not active for the user. Maybe if you explain a little more how you can use GetObject(), it can be combined with a file search (or WMI search) and you can accomplish you goal.

CreganTur
12-02-2009, 07:13 AM
You could use some conditionals to determine how you hook the object. If it fails for one, it should work for the other.

geekgirlau
12-02-2009, 08:25 PM
In a nutshell, this is what I have:

Access 2003 database frontend, SQL Server backend.
A number of reports setup as Excel templates, with a link to the database.
Reporting procedure creates a new workbook based on the nominated template, refreshes the data and (depending on the report) may run some additional procedures within the template.Methods attempted:

Set objXL = GetObject(, "Excel.Application") with late binding. This works if an instance of Excel is already running.
Set objXL = CreateObject("Excel.Application"). This fails - weird setup screen followed by Excel crashing in a big heap.
x = Shell(<path to Excel.EXE>, vbNormalFocus). This fails - see point 2.
Set objXL = GetObject(<path to Excel template>) with late binding. This opens Excel and the template, but then closes the workbook and leaves Excel open.
Set objXL = CreateObject(<path to Excel template>) with late binding. See point 4.

stanl
12-03-2009, 01:29 PM
Set objXL = GetObject(<path to Excel template>) with late binding. This opens Excel and the template, but then closes the workbook and leaves Excel open.


just a guess but what about


Set objXL = CreateObject(<path to Excel template>)
objXL.Application.Visible = True
objXL.Parent.Windows(1).Visible = True
'now manipulate the workbook


.02 Stan

geekgirlau
12-06-2009, 05:51 PM
Thanks for the suggestion Stan, but it's CreateObject that's causing the problem.

stanl
12-07-2009, 04:02 AM
Thanks for the suggestion Stan, but it's CreateObject that's causing the problem.

My bad. I meant
Set objXL = GetObject(<path To Excel template>)

geekgirlau
12-07-2009, 03:30 PM
Hi Stan,

Yep, tried that (item 4 in my list of methods attempted).

stanl
12-08-2009, 04:11 AM
Hi Stan,

Yep, tried that (item 4 in my list of methods attempted).

but you wrote that Item 4 opened the instance of Excel, just didn't display the workbook, that is why I added the 2 calls to .visible

don't suppose you could run the code outside of Access via VBS or WSH.

geekgirlau
12-08-2009, 04:17 PM
Thanks for your persistance with this Stan!

The actual sequence of events with this is:

Microsoft Office System Setup screen displays
Message appears stating that we're very sorry but MS Excel needs to close now
Excel actually remains open, and for a moment the template is visible
Template appears to close
Excel remains openIf you run the same procedure again, it skips the installation and the crash message, but steps 3 to 5 occur as before.

All of this occurs with CreateObject before the code ever hits the calls to visible. I know that the template is actually being launched - it has a "read-only recommended" message on it, which appears and waits for a response. However the template then disappears into the ether. The application is visible even prior to the Application.Visible command, and Parent.Windows(1).Visible just makes the Personal.xlsb workbook visible!

I'm officially putting this into the "weird and unavoidable behaviour" basket. Clearly there is something going on with the virtualisation that is affecting this. To my mind a message asking the user to manually launch Excel prior to running the reports is far less problematic then a setup screen and a faux Excel crash message!

Thanks for your help.

stanl
12-09-2009, 03:36 AM
Does sound wierd. Is there no way you can just turn on Report Services and move your queries to stored procs, or are these highly specialized templates. Or perhaps store the templates as binary objects, use an ADO stream to extract to a locally fixed file name - then use either Create or Get Object.:dunno

geekgirlau
12-10-2009, 11:11 PM
The answer appears to be something to do with the virtual installation of Access 2003. It's not a full install - there are multiple bits missing, such as the Linked Table Manager amongst other things.

As this is low priority amongst the powers that be, I have little chance of any changes being made to the virtual installation package (somewhere around the same time as hell freezing over I believe). Where you see "Solved" above, please read as "I've given up on finding a solution and will live with the far-from-arduous workaround".