Consulting

Results 1 to 6 of 6

Thread: Export VBA Macros to bas, text, into document, whatever

  1. #1
    VBAX Regular
    Joined
    Nov 2020
    Posts
    15
    Location

    Export VBA Macros to bas, text, into document, whatever

    Hi, I'm trying to export all macros that are in Word.
    I've tried tweaking what worked in Excel, to no avail.

    Then, I found the below code (author not listed). BUT, I'd like text to be saved instead of being shown in Msg boxes. The below code shows a Msg box for each macro.

    Can someone please help? I'd like to either have each macro pasted into one word document, or have each saved as a .bas file. Using a Mac as far as paths...

    Thanks!!
    -Ashley

    Sub GetCode()


    Dim prj As VBProject
    Dim comp As VBComponent
    Dim code As CodeModule
    Dim composedFile As String
    Dim i As Integer


    Set prj = ThisDocument.VBProject
    For Each comp In prj.VBComponents
    Set code = comp.CodeModule


    composedFile = comp.Name & vbNewLine


    For i = 1 To code.CountOfLines
    composedFile = composedFile & code.Lines(i, 1) & vbNewLine
    Next


    [-this is where I'd like a file save or paste code. Obviously, nothing with selection.copy worked ;-)]


    MsgBox composedFile
    Next


    End Sub

  2. #2
    The following will put all the code in a document each module to a new page.

    Sub GetCode()
    Dim oComp As Object
    Dim oCode As Object
    Dim i As Integer
    Dim oDoc As Document
    Dim oRng As Range
        If MsgBox("This could take a while!", _
                  vbInformation + vbOKCancel) = vbCancel Then Exit Sub
        Set oDoc = Documents.Add
        For Each oComp In ThisDocument.VBProject.VBComponents
            Set oRng = oDoc.Range
            If Len(oRng) > 2 Then
                oRng.Collapse 0
                oRng.InsertBreak wdPageBreak
            End If
            Set oCode = oComp.CodeModule
            oDoc.Range.InsertAfter "' " & oComp.Name & vbCr & vbCr
            For i = 1 To oCode.CountOfLines
                oDoc.Range.InsertAfter oCode.Lines(i, 1) & vbCr
                DoEvents
            Next
            DoEvents
        Next
        MsgBox "Completed!", vbInformation
    End Sub
    Graham Mayor - MS MVP (Word) 2002-2019
    Visit my web site for more programming tips and ready made processes
    http://www.gmayor.com

  3. #3
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,724
    Location
    One way


    Sub ExportModules()
        Dim sPath As String, sDoc As String, sFile As String
        Dim i As Long, iFile As Long, iComponentCount As Long
        Dim oComponent As VBComponent
    
    
        'get document info
        sPath = ActiveDocument.Path
        sDoc = ActiveDocument.Name
        i = InStrRev(sDoc, ".")
        sDoc = Left(sDoc, i - 1)
        
        
        'create output file name
        sFile = sPath & "\" & sDoc & ".txt"
        
        'delete if output file exists
        On Error Resume Next
        Kill sFile
        On Error GoTo 0
        
        'create new output file for write
        iFile = FreeFile
        Open sFile For Output As #iFile
    
    
    
    
        For Each oComponent In ActiveDocument.VBProject.VBComponents
            Print #iFile, "*********************************************************************"
            Print #iFile, "Start " & oComponent.Name
            Print #iFile, "*********************************************************************"
            
            For iComponentCount = 1 To oComponent.CodeModule.CountOfLines
                Print #iFile, oComponent.CodeModule.Lines(iComponentCount, 1)
            Next
            
            Print #iFile,
            Print #iFile, "*********************************************************************"
            Print #iFile, "End " & oComponent.Name
            Print #iFile, "*********************************************************************"
            Print #iFile,
            Print #iFile,
        Next
        Close #iFile
    
    
    End Sub
    PS -- the zip file is really a txt file, just change the extension
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  4. #4
    VBAX Regular
    Joined
    Nov 2020
    Posts
    15
    Location
    Thank you so much! Hilarious though, the first page only had two lines of text. I thought, bummer, did not work. Well, it did work, I just had to scroll down...

    I've been learning VBA and have made just a mess of everything. The resulting file will help me organize what works and trash my failed efforts. I try to put a 'YAY it works" comment at the top of successful macros ;-)

  5. #5
    VBAX Contributor
    Joined
    Jul 2020
    Location
    Sun Prairie
    Posts
    123
    Location
    You may want to visit the Word MVP vba pages.

  6. #6
    VBAX Regular
    Joined
    Nov 2020
    Posts
    15
    Location
    Thank you both! The macros work slightly differently and are both exactly what I wanted.
    I do not know why so many resources (including other forums) simply say it can't be done.

    Anyway, thank you for taking the time to help.

Tags for this Thread

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •