Macro Libraries problem on Win 7 64bit w/Office 2010

Steven Roemish

Macro Libraries problem on Win 7 64bit w/Office 2010
This past August I got a new machine to replace an old XP 32 bit machine that I kept around for running batch routines, testing and the like. This new machine also has Office 2010 where I've always had Office 2003.
Anyway, enough with the background, here's the problem. I've been struggling to edit all my VBA Macros on this new PC. Most of them will not open at all and others that do open give me errors about "Module not found".
The most recent issue just happened this morning. A VBA project that I keep all my test code and useful snippets that I steal from this forum failed to open; see error message below. I had used this very project just yesterday with great success. Now today, the VBA Editor will not even let me look at it. WHAT IS THE DEAL??

---------------------------
Warning
---------------------------
Some macro libraries could not be opened :

R:\software\CatiaAdmin\Scripts\testcode.catvba

Make sure the paths exist and check the libraries permissions.
---------------------------
OK
---------------------------

SteveR in Woolley, WA

Dave Frank

RE: Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Steven Roemish)

Hi Steve,

 

Could it be security settings?

 

Dave

Steven Roemish

Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Dave Frank)
Dave,
Can't see that being the issue if one day I can edit the macro and the next not.
I've been messing around with the reference libraries quite a bit. I've been able to open some macros after removing all the reference libraries on an XP machine then adding them back in on a W7 machine. I've come to the conclusion that it have more to do with Office 2010 DLLs more than with the OS, but I can't really confirm this.
I was really hoping someone else has had these issues and knew what to do.

SteveR.

Little Cthulhu

RE: Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Steven Roemish)

Hi.

As far as I know there are very FEW scenarious where moving to 64bit causes errors in VBA. While reference mechanism raise a LOT of errors even when migrating to another PC of the same architechture. So I guess your guess about Office dlls is pretty close to the true order of things. 

Anyhow, as you may already understand, I had similar difficulties when moved my XP 32bit CATIA vba libraries to W7 64bit PC. They worked first time I opened them but once I restarted CATIA session tons of errors rained over. So instead of adding existing catvba project I had to create a new project on W7 64bit and then copy-paste project contents module by module. I then realised that it was easier to do it using Export-Import commands. It was lame, but fighting VBA was never an option. 

So I believe that import-export is the way to go here. And today in a neighbour thread David Burke posted a nice solution of how to retrieve VBE object in catvba. This allowed me to present a following VBA module that automates export-import routine for the specified project. It has no UI, just a small amount of methods to make life easier.

Option Explicit
 
Sub CATMain()
   
'-------
' IMPORT
'-------
On Error Resume Next
Call ImportVBAComponents("VBAProject1", "C:\Temp\VBA\VBAProject1", True)
On Error GoTo 0
If (Err.Number <> 0) Then
Call MsgBox("Error while importing project components" + vbCr + Err.Description, _
vbCritical, _
"Import VBA Components")
 
Err.Clear
 
Else
Call MsgBox("Project components imported succesfully", _
vbInformation, _
"Import VBA Components")
End If
   
'-------
' EXPORT
'-------
On Error Resume Next
Call ExportVBAComponents("VBAProject1", "C:\Temp\VBA\VBAProject1", True)
On Error GoTo 0
If (Err.Number <> 0) Then
Call MsgBox("Error while exporting project components" + vbCr + Err.Description, _
vbCritical, _
"Export VBA Components")
 
Err.Clear
 
Else
Call MsgBox("Project components exported succesfully", _
vbInformation, _
"Export VBA Components")
End If
   
End Sub
     
'------------------------------------------------------------------------------
' GetActiveProjectFileName
'------------------------------------------------------------------------------
' Returns name of currently active VBA project.
'
'------------------------------------------------------------------------------
Public Function GetActiveProjectFileName() As String
 
' retrieve VBE object
Dim oVBE ' As VBE
Set oVBE = CreateObject("MSAPC.Apc").VBE
 
GetActiveProjectFileName = oVBE.ActiveVBProject.FileName
 
' do some cleanup
Set oVBE = Nothing
 
End Function
   
'------------------------------------------------------------------------------
' GetRunningProjectFileName
'------------------------------------------------------------------------------
' Returns name of currently running VBA project.
'
'------------------------------------------------------------------------------
Public Function GetRunningProjectFileName() As String
 
' retrieve VBE object
Dim oVBE ' As VBE
Set oVBE = CreateObject("MSAPC.Apc").VBE
 
Dim project ' As VBProject
Dim i As Integer
For i = 1 To oVBE.VBProjects.Count
' get next project
Set project = oVBE.VBProjects.Item(i)
 
' check project status
' vbext_vm_Run = 0
If (project.Mode = 0) Then
GetRunningProjectFileName = project.FileName
Exit For
End If
Next
 
' do some cleanup
Set project = Nothing
Set oVBE = Nothing
 
End Function
   
'------------------------------------------------------------------------------
' ExportVBAComponents
'------------------------------------------------------------------------------
' Exports components (classes, forms, modules) of the specified project to
' the target folder.
'
' Arguments:
 
' projectName -
' Name of a project to export components from.
' If name is empty ("") then components of active project are
' exported.
'
' folderPath -
' Path to a folder where components should be saved.
'
' createSubFolders -
' True if subfolders with names based on components type should
' be created. This way all modules will be saved in "Modules"
' subfolder.
' Naming rules can be adjusted in GetSubfolderByComponentType sub
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Public Sub ExportVBAComponents( _
ByVal projectName As String, _
ByVal folderPath As String, _
ByVal createSubfolders As Boolean)
 
' export all type of components
Call ExportVBAComponentsByType(projectName, folderPath, createSubfolders, vbext_ct_ActiveXDesigner)
Call ExportVBAComponentsByType(projectName, folderPath, createSubfolders, vbext_ct_ClassModule)
Call ExportVBAComponentsByType(projectName, folderPath, createSubfolders, vbext_ct_Document)
Call ExportVBAComponentsByType(projectName, folderPath, createSubfolders, vbext_ct_MSForm)
Call ExportVBAComponentsByType(projectName, folderPath, createSubfolders, vbext_ct_StdModule)
 
End Sub
 
'------------------------------------------------------------------------------
' ExportVBAComponentsByType
'------------------------------------------------------------------------------
' Exports components of a certain type of the specified project to
' the target folder.
'
' Arguments:
 
' projectName -
' Name of a project to export components from.
' If name is empty ("") then components of active project are
' exported.
'
' folderPath -
' Path to a folder where components should be saved.
'
' createSubFolders -
' True if subfolders with names based on components type should
' be created. This way all modules will be saved in "Modules"
' subfolder.
' Naming rules can be adjusted in GetSubfolderByComponentType sub
'
' componentType -
' Type of components to be exported.
'
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Public Sub ExportVBAComponentsByType( _
ByVal projectName As String, _
ByVal folderPath As String, _
ByVal createSubfolders As Boolean, _
ByVal componentType As vbext_ComponentType)
   
'------------------
' CHECK TARGET PATH
'------------------
Dim oFS
Set oFS = CreateObject("Scripting.FileSystemObject")
 
If Not (oFS.FolderExists(folderPath)) Then
 
' create folder if it doesn't exist
On Error Resume Next
Call oFS.CreateFolder(folderPath)
On Error GoTo 0
 
If (Err.Number <> 0) Then
' failed to create folder
Err.Raise vbError + 1, _
"ExportVBAComponents", _
"Target folder doesn't exist and cannot be created" + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
End If
   
'------------------
' EXPORT COMPONENTS
'------------------
' retrieve VBE object
Dim oVBE ' As VBE
Set oVBE = CreateObject("MSAPC.Apc").VBE
   
' access project
Dim project As VBProject
On Error Resume Next
If (Len(projectName) > 0) Then
Set project = oVBE.VBProjects.Item(projectName)
Else
Set project = oVBE.ActiveVBProject
End If
On Error GoTo 0
If (Err.Number <> 0) Then
Err.Raise vbError + 2, _
"ExportVBAComponentsByType", _
"Can't find VBA project with specified name: " + projectName + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
   
' loop through components
Dim component As VBComponent
For Each component In project.VBComponents
 
' export components of certain type
If (component.Type = componentType) Then
'------------------
' Build export path
'------------------
Dim exportPath As String
If (createSubfolders) Then
' determine subfolder name
Dim componentTypeFolder As String
componentTypeFolder = GetSubfolderByComponentType(componentType)
 
' create subfolder if necessary
exportPath = oFS.BuildPath(folderPath, componentTypeFolder)
 
If Not (oFS.FolderExists(exportPath)) Then
On Error Resume Next
Call oFS.CreateFolder(exportPath)
On Error GoTo 0
 
If (Err.Number <> 0) Then
' failed to create subfolder
Err.Raise vbError + 3, _
"ExportVBAComponents", _
"Subfolder " + componentTypeFolder + " doesn't exist and cannot be created" + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
End If
Else
' don't use subfolders
exportPath = folderPath
End If
 
' append component's name with proper extension
exportPath = oFS.BuildPath(exportPath, component.Name + "." + GetFileExtensionByComponentType(componentType))
 
'-------
' Export
'-------
On Error Resume Next
Call component.Export(exportPath)
On Error GoTo 0
 
If (Err.Number <> 0) Then
Err.Raise vbError + 4, _
"ExportVBAComponents", _
"Error exporting component " + component.Name + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
 
End If
Next
   
' do some cleanup
Set oFS = Nothing
Set oVBE = Nothing
 
End Sub
     
'------------------------------------------------------------------------------
' ImportVBAComponents
'------------------------------------------------------------------------------
' Exports components (classes, forms, modules) of the specified project to
' the target folder.
'
' Arguments:
 
' projectName -
' Name of a project to export components from.
' If name is empty ("") then components of active project are
' exported.
'
' folderPath -
' Path to a folder where components should be saved.
'
' searchSubfoldersOnly -
' True if subfolders with the names based on component types
' should be searched instead of folder from folderPath.
' Naming rules can be adjusted in GetSubfolderByComponentType sub
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Public Sub ImportVBAComponents( _
ByVal projectName As String, _
ByVal folderPath As String, _
ByVal searchSubfoldersOnly As Boolean)
 
' export all type of components
Call ImportVBAComponentsByType(projectName, folderPath, searchSubfoldersOnly, vbext_ct_ActiveXDesigner)
Call ImportVBAComponentsByType(projectName, folderPath, searchSubfoldersOnly, vbext_ct_ClassModule)
Call ImportVBAComponentsByType(projectName, folderPath, searchSubfoldersOnly, vbext_ct_Document)
Call ImportVBAComponentsByType(projectName, folderPath, searchSubfoldersOnly, vbext_ct_MSForm)
Call ImportVBAComponentsByType(projectName, folderPath, searchSubfoldersOnly, vbext_ct_StdModule)
 
End Sub
   
'------------------------------------------------------------------------------
' ImportVBAComponentsByType
'------------------------------------------------------------------------------
' Import components of a certain type to the specified project from the
' target folder.
'
' Arguments:
 
' projectName -
' Name of a project to import components to.
' If name is empty ("") then components of active project are
' exported.
'
' folderPath -
' Path to a folder where components should be saved.
'
' searchSubfoldersOnly -
' True if subfolders with the names based on component types
' should be searched instead of folder from folderPath.
' Naming rules can be adjusted in GetSubfolderByComponentType sub
'
' componentType -
' Type of components to be imported.
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Public Sub ImportVBAComponentsByType( _
ByVal projectName As String, _
ByVal folderPath As String, _
ByVal searchSubfoldersOnly As Boolean, _
ByVal componentType As vbext_ComponentType)
   
'------------------
' CHECK FOLDER PATH
'------------------
Dim oFS
Set oFS = CreateObject("Scripting.FileSystemObject")
 
If Not (oFS.FolderExists(folderPath)) Then
 
' failed to find folder
Err.Raise vbError + 1, _
"ImportVBAComponentsByType", _
"Target folder doesn't exist"
End If
   
'------------------
' IMPORT COMPONENTS
'------------------
' retrieve VBE object
Dim oVBE ' As VBE
Set oVBE = CreateObject("MSAPC.Apc").VBE
   
' access project
Dim project As VBProject
On Error Resume Next
If (Len(projectName) > 0) Then
Set project = oVBE.VBProjects.Item(projectName)
Else
Set project = oVBE.ActiveVBProject
End If
On Error GoTo 0
If (Err.Number <> 0) Then
Err.Raise vbError + 2, _
"ImportVBAComponentsByType", _
"Can't find VBA project with specified name: " + projectName + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
 
'------------------
' Build import path
'------------------
Dim importPath As String
If (searchSubfoldersOnly) Then
' determine subfolder name
Dim componentTypeFolder As String
componentTypeFolder = GetSubfolderByComponentType(componentType)
 
importPath = oFS.BuildPath(folderPath, componentTypeFolder)
Else
' don't use subfolders
importPath = folderPath
End If
 
If (oFS.FolderExists(importPath)) Then
 
' get files in the folder
Dim folder As Object
Set folder = oFS.GetFolder(importPath)
 
Dim file As Object
For Each file In folder.Files
'-------
' Import
'-------
Dim component As VBComponent
On Error Resume Next
Set component = project.VBComponents.Import(file.path)
On Error GoTo 0
 
If (Err.Number <> 0) Then
Err.Raise vbError + 3, _
"ImportVBAComponentsByType", _
"Error exporting component " + component.Name + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
 
' remove component if it's type differs from desired one
If Not (component.Type = componentType) Then
Call project.VBComponents.Remove(component)
End If
Next
Else
' subfolder doesn't exist
End If
   
' do some cleanup
Set oFS = Nothing
Set oVBE = Nothing
 
End Sub
     
'------------------------------------------------------------------------------
' ImportVBAComponentFromFile
'------------------------------------------------------------------------------
' Imports component from the specified file to the project.
'
' Arguments:
 
' projectName -
' Name of a project to export components from.
' If name is empty ("") then component is imported in the
' active project.
'
' filePath -
' Path to a file, containing component defition.
'
'------------------------------------------------------------------------------
Public Sub ImportVBAComponentFromFile( _
ByVal projectName As String, _
ByVal filePath As String)
   
' retrieve VBE object
Dim oVBE ' As VBE
Set oVBE = CreateObject("MSAPC.Apc").VBE
   
' access project
Dim project ' As VBProject
On Error Resume Next
If (Len(projectName) > 0) Then
Set project = oVBE.VBProjects.Item(projectName)
Else
Set project = oVBE.ActiveVBProject
End If
On Error GoTo 0
If (Err.Number <> 0) Then
Err.Raise vbError + 2, _
"ExportVBAComponentsByType", _
"Can't find VBA project with specified name: " + projectName + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
   
' import component
On Error Resume Next
Call project.VBComponents.Import(FileName)
On Error GoTo 0
If (Err.Number <> 0) Then
Err.Raise vbError + 5, _
"ExportVBAComponentsByType", _
"Can't import specified file to the project" + vbCr + _
vbCr + _
"Original Error: " + vbCr + _
Err.Description
End If
   
' do some cleanup
Set oVBE = Nothing
 
End Sub
 
'------------------------------------------------------------------------------
' GetSubfolderByComponentType
'------------------------------------------------------------------------------
' Service method that returns name of subfolder that corresponds to the
' specified component type. Used in export methods for subfolder generation.
'
' Arguments:
'
' componentType -
' Type of component.
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Private Function GetSubfolderByComponentType(ByVal componentType As vbext_ComponentType) As String
 
' determine subfolder name
Select Case componentType
Case vbext_ct_ActiveXDesigner
GetSubfolderByComponentType = "ActiveX"
 
Case vbext_ct_ClassModule
GetSubfolderByComponentType = "Classes"
 
Case vbext_ct_Document
GetSubfolderByComponentType = "Documents"
 
Case vbext_ct_MSForm
GetSubfolderByComponentType = "Forms"
 
Case vbext_ct_StdModule
GetSubfolderByComponentType = "Modules"
 
Case Else
GetSubfolderByComponentType = "Other"
End Select
 
End Function
 
'------------------------------------------------------------------------------
' GetFileExtensionByComponentType
'------------------------------------------------------------------------------
' Service method that returns file extension that corresponds to the
' specified component type. Used in export methods for component file naming.
'
' Arguments:
'
' componentType -
' Type of component.
'
'------------------------------------------------------------------------------
' REQUIRES
'------------------------------------------------------------------------------
' Microsoft Visual Basic for Applications Extensibility 5.3 reference
'------------------------------------------------------------------------------
Private Function GetFileExtensionByComponentType(ByVal componentType As vbext_ComponentType) As String
 
' determine subfolder name
Select Case componentType
Case vbext_ct_ActiveXDesigner
GetFileExtensionByComponentType = "ocx"
 
Case vbext_ct_ClassModule
GetFileExtensionByComponentType = "cls"
 
Case vbext_ct_Document
GetFileExtensionByComponentType = "doc"
 
Case vbext_ct_MSForm
GetFileExtensionByComponentType = "frm"
 
Case vbext_ct_StdModule
GetFileExtensionByComponentType = "bas"
 
Case Else
GetFileExtensionByComponentType = "vbc"
End Select
 
End Function

 



Attachments

  • VBAProject.txt (21.9k)

Steven Roemish

Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Little Cthulhu)
Little,
Your help in VBA matters has been invaluable; may your forum karma double and give yourself a gold star.
I have done a little of what you suggested; to start a new project and simply rewrite the code (Copy and paste that is) and it seems to be the most reliable solution. I found that exporting and importing the modules is ok but user forms still give me problems; "Module not found" errors. Kind of weird.
For projects that VBA actually allows me to open, I have tried removing all reference libraries then adding them back a few at a time. This worked with limited success. For projects that VBA will not let me open on my W7 machine, I will have to somehow find an XP machine that has not been replaced yet and extract the user forms, modules, and classes. It just sounds so ridicules to have to do. The worst thing about it is in a few cases I'll have to rebuilt my user forms which can get quite elaborate.
I will try your code out and let you know how it works.
Thanks again for providing all your code snippets

SteveR.

Little Cthulhu

RE: Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Steven Roemish)
What about userforms?
Does "module not found" error pops up when you export them to .frm and then import to another project or when you try to run newly imported form?

Steven Roemish

Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Little Cthulhu)
Upon importing of the .frm form in the new project I get the error "module not found" and I can't import it. sometimes it imports it but won't let me edit it.

SteveR.

Little Cthulhu

RE: Macro Libraries problem on Win 7 64bit w/Office 2010
(in response to Steven Roemish)
Wow.
Observed similar behaviour only when form contained custom activex controls that were missing on a target machine. Can this be the case?