Marty: Thanks for your response. At least I'm not crazy or alone -- well, maybe we both are.
I really like your idea of the Master Workbook to hold code and sheet templates. I can see that as being a great way to store a documentation sheet for the workbook, constants as named ranges, conversion tables, and hyperlinks to the web as applicable. I wonder if content of some of those sheets could also be linked to master versions (i.e. you never know when they are going to change the value of Pi or something). The idea of something equivalent to Custom.dic for code is also really attractive. I hope Microsoft is taking notes.
I'm a personal user and don't have access to SharePoint that I'm aware of. I do love using OneNote to supplement my aging memory and recording solutions to various problems I've had. In one of my last pre-retirement projects, I worked on a coding project that I intended for a prospective client and I kept that code in its own Master Workbook and Master Document that would likely have ended up being a pair of Add-ins. I think I may go back with that approach rather than the Personal.xlsb and its Word equivalent. After all, who am I to mess around with someone's Personal.xlsb etc.
I still use the VBA editor to write and maintain my code to gain access to IntelliSense. As you may know, a lot of editing can introduce instability into code and can be re-stabilized by Exporting and Importing the VBA. Ron de Bruin had a couple of routines for doing this that he posted at
Import and Export VBA code. I found this to be really effective in solving problems that get introduced by the compiler or some other ghost in the machine. I also found it to be a means for maintaining the same code in Excel and Word procedure libraries.
I adapted Ron's code for use with Word or Excel and generalized the code so it works with both applications without any real-time changes. I tend to work heavily in Word or heavily in Excel. Between bouts of heavy editing and after doing a RefreshModules on the newly edited code, I re-import all the code into the version for Word or Excel that has been superseded by the editing. I keep the following code in its own module that is stored independently from my procedure libraries. Redundantly keeping it in the procedure libraries for Excel/Word assures it is always available if my work migrates to another machine. I tried to make sure it is well documented and robust enough to work on a machine other than my own. YMMV.
Ron: Thanks for all you do. I hope this is in keeping with accepted use of your generous contributions.
VBA Code:
Option Explicit
Private Sub RefreshModules()
Export
Import
End Sub
Private Sub Export()
Select Case Application
Case "Microsoft Excel"
ExportModulesFromExcelWorkbook
Case "Microsoft Word"
ExportModulesFromWordDocument
End Select
End Sub
Private Sub Import()
Select Case Application
Case "Microsoft Excel"
ImportModulesToExcelWorkbook
Case "Microsoft Word"
ImportModulesToWordDocument
End Select
End Sub
Private Sub ExportModulesFromWordDocument()
Dim appWord As Object
Dim MySource As Object
Dim cmpComponent As Object
#Else
Dim appWord As Word.Application
Dim MySource As Word.Document
Dim cmpComponent As VBIDE.VBComponent
On Error Resume Next
Set appWord = GetObject(, "Word.Application")
If Err Then
MsgBox "Word is not running." & vbCr & _
"There is nothing to Export from Word.", vbOKOnly
Exit Sub
End If
On Error GoTo 0
Dim bExport As Boolean
Dim szSourceDocument As String
Dim szExportPath As String
Dim szFileName As String
If FolderWithVBAProjectFiles = "Error" Then
MsgBox "Export Folder not exist"
Exit Sub
End If
On Error Resume Next
Kill FolderWithVBAProjectFiles & "\*.*"
On Error GoTo 0
szSourceDocument = appWord.ActiveDocument.Name
Set MySource = appWord.Application.Documents(szSourceDocument)
If MySource.VBProject.Protection = 1 Then
MsgBox "The VBA in this Document is protected," & _
"not possible to export the code"
Exit Sub
End If
szExportPath = FolderWithVBAProjectFiles & "\"
For Each cmpComponent In MySource.VBProject.VBComponents
bExport = True
szFileName = cmpComponent.Name
Select Case cmpComponent.Type
Case vbext_ct_ClassModule
szFileName = szFileName & ".cls"
Case vbext_ct_MSForm
szFileName = szFileName & ".frm"
Case vbext_ct_StdModule
szFileName = szFileName & ".bas"
Case vbext_ct_Document
bExport = False
End Select
If bExport Then
cmpComponent.Export szExportPath & szFileName
End If
Next cmpComponent
MsgBox "Export is ready"
End Sub
Private Sub ExportModulesFromExcelWorkbook()
Dim appExcel As Object
Dim wkbSource As Object
Dim cmpComponent As Object
#Else
Dim appExcel As Excel.Application
Dim wkbSource As Excel.Workbook
Dim cmpComponent As VBIDE.VBComponent
On Error Resume Next
Set appExcel = GetObject(, "Excel.Application")
If Err Then
MsgBox "Excel is not running." & vbCr & _
"There is nothing to Export from Excel.", vbOKOnly
Exit Sub
End If
On Error GoTo 0
Dim bExport As Boolean
Dim szSourceWorkbook As String
Dim szExportPath As String
Dim szFileName As String
If FolderWithVBAProjectFiles = "Error" Then
MsgBox "Export Folder not exist"
Exit Sub
End If
On Error Resume Next
Kill FolderWithVBAProjectFiles & "\*.*"
On Error GoTo 0
szSourceWorkbook = appExcel.ActiveWorkbook.Name
Set wkbSource = appExcel.Application.Workbooks(szSourceWorkbook)
If wkbSource.VBProject.Protection = 1 Then
MsgBox "The VBA in this workbook is protected," & _
"not possible to export the code"
Exit Sub
End If
szExportPath = FolderWithVBAProjectFiles & "\"
For Each cmpComponent In wkbSource.VBProject.VBComponents
bExport = True
szFileName = cmpComponent.Name
Select Case cmpComponent.Type
Case vbext_ct_ClassModule
szFileName = szFileName & ".cls"
Case vbext_ct_MSForm
szFileName = szFileName & ".frm"
Case vbext_ct_StdModule
szFileName = szFileName & ".bas"
Case vbext_ct_Document
bExport = False
End Select
If bExport Then
cmpComponent.Export szExportPath & szFileName
End If
Next cmpComponent
MsgBox "Export is ready"
End Sub
Private Sub ImportModulesToExcelWorkbook()
Dim appExcel As Object
Dim wkbTarget As Object
Dim objFSO As Object
Dim objFile As Object
Dim cmpComponents As Object
#Else
Dim appExcel As Excel.Application
Dim wkbTarget As Excel.Workbook
Dim objFSO As Scripting.FileSystemObject
Dim objFile As Scripting.File
Dim cmpComponents As VBIDE.VBComponents
On Error Resume Next
Set appExcel = GetObject(, "Excel.Application")
If Err Then
Set appExcel = CreateObject("Excel.Application")
End If
On Error GoTo 0
Dim szTargetWorkbook As String
Dim szImportPath As String
Dim szFileName As String
If ActiveWorkbook.Name = ThisWorkbook.Name Then
MsgBox "Select another destination workbook" & _
"Not possible to import in this workbook "
Exit Sub
End If
If FolderWithVBAProjectFiles = "Error" Then
MsgBox "Import Folder not exist"
Exit Sub
End If
szTargetWorkbook = appExcel.ActiveWorkbook.Name
Set wkbTarget = appExcel.Application.Workbooks(szTargetWorkbook)
If wkbTarget.VBProject.Protection = 1 Then
MsgBox "The VBA in this workbook is protected," & _
"not possible to Import the code"
Exit Sub
End If
szImportPath = FolderWithVBAProjectFiles & "\"
Set objFSO = New Scripting.FileSystemObject
If objFSO.GetFolder(szImportPath).Files.Count = 0 Then
MsgBox "There are no files to import"
Exit Sub
End If
Call DeleteVBAModulesAndUserFormsFromExcelWorkbook
Set cmpComponents = wkbTarget.VBProject.VBComponents
For Each objFile In objFSO.GetFolder(szImportPath).Files
If (objFSO.GetExtensionName(objFile.Name) = "cls") Or _
(objFSO.GetExtensionName(objFile.Name) = "frm") Or _
(objFSO.GetExtensionName(objFile.Name) = "bas") Then
cmpComponents.Import objFile.Path
End If
Next objFile
MsgBox "Import is ready"
End Sub
Private Sub ImportModulesToWordDocument()
Dim appWord As Object
Dim cmpComponents As Object
Dim MyTarget As Object
Dim objFSO As Object
Dim objFile As Object
#Else
Dim appWord As Word.Application
Dim cmpComponents As VBIDE.VBComponents
Dim MyTarget As Word.Document
Dim objFSO As Scripting.FileSystemObject
Dim objFile As Scripting.File
On Error Resume Next
Set appWord = GetObject(, "Word.Application")
If Err Then
Set appWord = CreateObject("Word.Application")
End If
On Error GoTo 0
Dim szMyTarget As String
Dim szImportPath As String
Dim szFileName As String
If appWord.ActiveDocument.Name = ThisDocument.Name Then
MsgBox "Select another destination Document" & _
"Not possible to import in this Document "
Exit Sub
End If
If FolderWithVBAProjectFiles = "Error" Then
MsgBox "Import Folder not exist"
Exit Sub
End If
szMyTarget = appWord.ActiveDocument.Name
Set MyTarget = appWord.Application.Documents(szMyTarget)
If MyTarget.VBProject.Protection = 1 Then
MsgBox "The VBA in this Document is protected," & _
"not possible to Import the code"
Exit Sub
End If
szImportPath = FolderWithVBAProjectFiles & "\"
Set objFSO = New Scripting.FileSystemObject
If objFSO.GetFolder(szImportPath).Files.Count = 0 Then
MsgBox "There are no files to import"
Exit Sub
End If
DeleteVBAModulesAndUserFormsFromWordDocument
Set cmpComponents = MyTarget.VBProject.VBComponents
For Each objFile In objFSO.GetFolder(szImportPath).Files
If (objFSO.GetExtensionName(objFile.Name) = "cls") Or _
(objFSO.GetExtensionName(objFile.Name) = "frm") Or _
(objFSO.GetExtensionName(objFile.Name) = "bas") Then
cmpComponents.Import objFile.Path
End If
Next objFile
MsgBox "Import is ready"
End Sub
Private Function FolderWithVBAProjectFiles() As String
Dim WshShell As Object
Dim FSO As Object
Dim SpecialPath As String
Set WshShell = CreateObject("WScript.Shell")
Set FSO = CreateObject("scripting.filesystemobject")
SpecialPath = WshShell.SpecialFolders("MyDocuments")
If Right$(SpecialPath, 1) <> "\" Then
SpecialPath = SpecialPath & "\"
End If
If FSO.FolderExists(SpecialPath & "VBAProjectFiles") = False Then
On Error Resume Next
MkDir SpecialPath & "VBAProjectFiles"
On Error GoTo 0
End If
If FSO.FolderExists(SpecialPath & "VBAProjectFiles") = True Then
FolderWithVBAProjectFiles = SpecialPath & "VBAProjectFiles"
Else
FolderWithVBAProjectFiles = "Error"
End If
End Function
Private Function DeleteVBAModulesAndUserFormsFromExcelWorkbook() As Variant
Dim appExcel As Object
Dim VBProj As Object
Dim VBComp As Object
#Else
Dim appExcel As Excel.Application
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
On Error Resume Next
Set appExcel = GetObject(, "Excel.Application")
If Err Then
Set appExcel = CreateObject("Excel.Application")
End If
On Error GoTo 0
Set VBProj = appExcel.ActiveWorkbook.VBProject
For Each VBComp In VBProj.VBComponents
If VBComp.Type = vbext_ct_Document Then
Else
VBProj.VBComponents.Remove VBComp
End If
Next VBComp
End Function
Private Function DeleteVBAModulesAndUserFormsFromWordDocument() As Variant
Dim appWord As Object
Dim VBProj As Object
Dim VBComp As Object
#Else
Dim appWord As Word.Application
Dim VBProj As VBIDE.VBProject
Dim VBComp As VBIDE.VBComponent
On Error Resume Next
Set appWord = GetObject(, "Word.Application")
If Err Then
MsgBox "Word is not running." & vbCr & _
"There is nothing to Delete from Word.", vbOKOnly
Exit Function
End If
On Error GoTo 0
Set VBProj = appWord.ActiveDocument.VBProject
For Each VBComp In VBProj.VBComponents
If VBComp.Type = vbext_ct_Document Then
Else
VBProj.VBComponents.Remove VBComp
End If
Next VBComp
End Function