Forum Discussion

perkin_warbeck's avatar
perkin_warbeck
Brass Contributor
Mar 05, 2024

Why do vba worksheet modules export as .cls modules?

I would like to clean up my Excel VBA project by exporting all code modules and then re-importing them. I understand that there is no VBA Project export or import, and that this must be done one module at a time. I only have 10-15 modules in the project, so I am not willing to pay for software if I can do it myself. I will do it manually (not I'm not looking for code to automate the process).

 

In VBE Project Explorer, when I a export a module in the Modules folder, it is written out as a .bas file, and I have no problem importing it. However, when I export a module in the Microsoft Excel Objects folder (e.g., Sheet1), it is written out as a .cls file.  When I import it, it goes into the Class folder, rather than the Microsoft Excel Objects folder. I'm wondering whether this is an Excel bug, or if there is something I can do to fix it.

 

The screenshot below shows the VBE project explorer before and after "cleanup." In the After screenshot, Sheet2 does not have any code. I had to create Sheet2 because a Workbook needs at least one worksheet.

  • peiyezhu's avatar
    peiyezhu
    Bronze Contributor

    perkin_warbeck 

     

    Attribute VB_Name = "Mod_Vba"
    ' DESCRIPTION
    '   This module can export and inport module by Workbook_BeforeSave event. Thus the files can be managed by version
    '   control tools or edited in other IDE then imported back.
    ' USAGE
    '   1. Import this module to a workbook.
    '   2. In the Workbook_BeforeSave event, add: Syn "FULL_PATH_TO_YOUR_MODULE_FILE", "MODULE_NAME". eg.
    '        Private Sub Workbook_BeforeSave(ByVal SaveAsUI As Boolean, Cancel As Boolean)
    '            Syn "C:\projects\vba_lib\Mod_Vba.bas", "Mod_Vba"
    '            Syn "C:\projects\vba_lib\Mod_Debug.bas"    ' If omit the module name, the module will be named as the file
    '        End Sub
    '   3. Save the workbook. The module will be imported.
    '   4. Change the file in some 3rd-party editor and save. Save the workbook, the module will be imported.
    '   5. Change the module code in VBA Editor. Save the workbook, the module will be exported.
    ' NOTE
    '   * Path string in this module must be ended with "\"
    '   * Path provided to Syn() must be absolute path
    '   * This module should be named as 'Mod_Vba', otherwise need to change predefined name in ImportModule() accordingly
    
    Option Explicit
    Option Base 1
    
    Public Function Syn(ByVal sFile As String, Optional ByVal sModule As String)
        Dim bModule As Boolean, bFile As Boolean
    
        ' Check if file exists
        bFile = (Dir(sFile) <> "")
    
        ' Use file name as module name if not specified
        If sModule = "" Then
            sModule = Mid(sFile, InStrRev(sFile, "\") + 1)          ' Get file name
            sModule = Left(sModule, InStrRev(sModule, ".") - 1)   ' Remove extension
        End If
    
        ' Check if module exists
        bModule = InCollection(sModule, ActiveWorkbook.VBProject.VBComponents)
    
        If bFile = True And bModule = False Then
            ' Import the file if no module
            ImportModule sFile, sModule
        ElseIf bFile = False And bModule = True Then
            ' Export the module if no file
            ExportModule sModule, sFile
        ElseIf bFile = True And bModule = True Then
            Dim nDateDiff As Double
            nDateDiff = CDbl(Format(FileDateTime(sFile), "YYYYMMDDHHMMSS"))
            nDateDiff = nDateDiff - CDbl(GetModuleStamp(sModule))
            If nDateDiff > 0 Then
                ' Import the file if it is newer.
                ' NOTE: Any modification of module in VBE will be overwritten.
                ImportModule sFile, sModule
            ElseIf ActiveWorkbook.VBProject.VBComponents(sModule).Saved = False _
                Or nDateDiff < 0 Then
                ' Export if module is modified while file remains.
                ExportModule sModule, sFile
            Else
                Debug.Print "Synchronised " & sFile & " with " & sModule
                Exit Function
            End If
        Else
            Err.Raise 1, "Mod_Vba\Syn", "Neither file nor module are found."
            Exit Function
        End If
    
        Syn = SetModuleStamp(sModule, sFile)
        Debug.Print "Synchronised " & sFile & " with " & sModule
    
    End Function
    
    Public Function InCollection(Item As Variant, Parent As Variant) As Boolean
        On Error Resume Next
        Parent.Item Item
        InCollection = (Err.Number = 0)
        On Error GoTo 0
    End Function
    
    Private Function GetModuleStamp(ByVal sModule As String) As String
        If Not InCollection(sModule, ActiveWorkbook.VBProject.VBComponents) Then Exit Function
    
        GetModuleStamp = ActiveWorkbook.VBProject.Description
    
        Dim nPos As Long
        nPos = InStr(1, GetModuleStamp, sModule)
        If nPos > 0 Then GetModuleStamp = Mid(GetModuleStamp, nPos + Len(sModule) + 1, 14) Else GetModuleStamp = "0"
    
        Debug.Print sModule & " stamp: " & GetModuleStamp
    End Function
    
    Private Function SetModuleStamp(ByVal sModule As String, ByVal TimeStamp) As String
        If Not InCollection(sModule, ActiveWorkbook.VBProject.VBComponents) Then Exit Function
    
        Dim sTimeStamp As String
    
        ' If TimeStamp is a file String then get the FileDateTime, else it is provided as a Date
        If TypeName(TimeStamp) = "String" Then TimeStamp = FileDateTime(TimeStamp)
    
        TimeStamp = Format(TimeStamp, "YYYYMMDDHHMMSS")
    
        ' Store module timestamp in VBProject.Desciption
        ' Format: ModuleName@YYYYMMDDHHMMSS,ModuleName@YYYYMMDDHHMMSS
        Dim nPos As Long
    
        SetModuleStamp = ActiveWorkbook.VBProject.Description
    
        ' Find the module position in timestamp string
        nPos = InStr(1, SetModuleStamp, sModule)
        If nPos > 0 Then
            ' If module found, update the timestamp
            SetModuleStamp = Left(SetModuleStamp, nPos - 1) & sModule & "@" & TimeStamp & "," & Mid(SetModuleStamp, nPos + Len(sModule) + 16)
        Else
            'Module not found, append the new timestamp
            SetModuleStamp = SetModuleStamp & sModule & "@" & TimeStamp & ","
        End If
        ActiveWorkbook.VBProject.Description = SetModuleStamp
    
        Debug.Print "Module stamp updated: " & SetModuleStamp
    End Function
    
    Public Function ImportModule(ByVal sFile As String, Optional ByVal sModule As String, Optional ByVal sWorkbookName As String = "") As String
        Dim wbSource As Excel.Workbook
        Dim oVBC
    
        ' Use ActiveWorkbook by default
        If sWorkbookName = "" Then sWorkbookName = ActiveWorkbook.Name
        Set wbSource = Application.Workbooks(sWorkbookName)
    
        Set oVBC = ActiveWorkbook.VBProject.VBComponents
    
        ' Use file name as module name if not specified
        If sModule = "" Then
            sModule = Mid(sFile, InStrRev(sFile, "\") + 1)          ' Get file name
            sModule = Left(sModule, InStrRev(sModule, ".") - 1)   ' Remove extension
        End If
    
        ' Check if module exists
        If InCollection(sModule, oVBC) Then
            ' If module exists, rename old module
            oVBC(sModule).Name = sModule & "__Old__"
    
            ' Import the new module and rename
            oVBC.import sFile
            oVBC(oVBC.Count).Name = sModule
    
            ' For this module, the timestamp needs to be set before removing.
            If sModule = "Mod_Vba" Then SetModuleStamp sModule, sFile
    
            ' Delete the old module
            oVBC.Remove oVBC(sModule & "__Old__")
        Else
            ' If module does not exist, import and rename
            oVBC.import sFile
            oVBC(oVBC.Count).Name = sModule
        End If
        ImportModule = sModule
    
        Debug.Print sModule & " imported from " & sFile
    End Function
    
    Public Function ExportModule(Optional ByVal sModule As String = "", Optional ByVal sPath As String = "", Optional ByVal sWorkbookName As String = "")
        Dim sFile As String, sExt As String
        Dim wbSource As Excel.Workbook
        Dim oVBC
    
        ' Use ActiveWorkbook by default
        If sWorkbookName = "" Then sWorkbookName = ActiveWorkbook.Name
        Set wbSource = Application.Workbooks(sWorkbookName)
    
        If wbSource.VBProject.Protection = 1 Then
            Debug.Print "Error: The VBA in this workbook is protected, not possible to export the code."
            Exit Function
        End If
    
        ' Use workbook folder by default
        If sPath = "" Then sPath = wbSource.path & "\"
    
        If sModule = "" Then
            ' Export all modules if not specified
            For Each oVBC In wbSource.VBProject.VBComponents
                ' Match file extension with module type
                sExt = ModuleTypeExt(oVBC.Type)
                sFile = sPath & oVBC.Name & sExt
                If sExt <> "" Then oVBC.Export sFile
                Debug.Print sModule & " exported to " & sFile
            Next
        ElseIf InCollection(sModule, wbSource.VBProject.VBComponents) Then
            ' Export specific module
            Set oVBC = wbSource.VBProject.VBComponents(sModule)
            If Right(sPath, 1) = "\" Then
                ' If only path is given, use module name as file name
                sExt = ModuleTypeExt(oVBC.Type)
                sFile = sPath & oVBC.Name & sExt
            Else
                ' If full path is given
                sFile = sPath
            End If
            oVBC.Export sFile
            Debug.Print sModule & " exported to " & sFile
        End If
    End Function
    
    Private Function ModuleTypeExt(ByVal nModuleType) As String
        ' Check VBComponent.Type
        Select Case nModuleType
            Case 1
                ModuleTypeExt = ".bas"
            Case 2
                ModuleTypeExt = ".cls"
            Case 3
                ModuleTypeExt = ".frm"
            Case Else
                ' Worksheet or workbook object.
                ModuleTypeExt = ""
        End Select
    End Function

    I am not sure it is bug or not.

    I used to run above VBA to export and import codes.

    Hope helpful.

    • perkin_warbeck's avatar
      perkin_warbeck
      Brass Contributor
      Thank you for sharing your code. In function ModuleTypeExt, Worksheet or Workbook objects are exported without an extension. They will be imported as class modules, which is wrong. That's the problem I'm trying to solve: how to export and import Worksheet or Workbook objects. So maybe it's impossible.
      • HansVogelaar's avatar
        HansVogelaar
        MVP

        perkin_warbeck 

        Worksheet and workbook modules ARE class modules, but not stand-alone class modules. You cannot use File > Import to import them to a worksheet or workbook. You have to copy/paste the text.

    • peiyezhu's avatar
      peiyezhu
      Bronze Contributor
      'Export all VBE modules instead of one by one

      ```vba
      ' Precondition:
      ''1. Reference Microsoft Visual Basic for Application Extensibility 5.3,
      ''2. Enable access to VBA project (Trust access to the VBA project)

      Sub ExportVBEModules()
      Dim ExportPath As String, ExtendName As String
      Dim vbc As VBComponent
      Dim i%

      ExportPath = ThisWorkbook.Path

      For Each vbc In Application.VBE.ActiveVBProject.VBComponents
      ' Get the number of lines of code in the module
      i = ThisWorkbook.VBProject.VBComponents(vbc.Name).CodeModule.CountOfLines

      '' Check if the module is not empty, i.e., if the number of lines of code is >= 1.
      If i >= 1 Then
      Select Case vbc.Type
      Case vbext_ct_ClassModule, vbext_ct_Document ' Component type is Class Module, Excel Object
      ExtendName = ".Cls" ' Set the file extension for export
      Case vbext_ct_MSForm ' Component type is UserForm
      ExtendName = ".frm"
      Case vbext_ct_StdModule ' Component type is Standard Module
      ExtendName = ".Bas"
      End Select
      If ExtendName <> "" Then
      vbc.Export ExportPath & "\" & vbc.Name & ExtendName
      End If
      End If
      Next

      End Sub
      ```

      This VBA macro is used to batch export the code of VBE modules in the current workbook to a specified path.

Resources