List macros in a presentation

The ListMacrosInPresentation() routine takes an Presentation object and a Collection object as input. In the Collection object, it returns the macros that are within the presentation. You need to include a reference to Microsoft Visual Basic for Applications Extensibility through Tools | References... menu item in VBA Editor.

Function GetProcedureFromLine(ByVal CM As CodeModule, _
    ByRef StartLine As Long) As String

    Dim I As Long
    Dim S As String

    I = StartLine
    Do While I < CM.CountOfLines
        S = CM.ProcOfLine(I, vbext_pk_Proc)
        If S <> "" Then
            Exit Do
        End If

        I = I + 1
    Loop

    If S <> "" Then
        StartLine = I
        GetProcedureFromLine = S
    End If
End Function

Sub ListMacrosInPresentation(ByVal Pres As Presentation, _
    ByVal C As Collection)

    Dim I As Long
    Dim StartLine As Long
    Dim ProcName As String

    With Pres.VBProject
        For I = 1 To .VBComponents.Count
            With .VBComponents(I)
                StartLine = .CodeModule.CountOfDeclarationLines + 1
                Do While StartLine < .CodeModule.CountOfLines
                    ProcName = GetProcedureFromLine(.CodeModule, _
                        StartLine)
                    If ProcName = "" Then
                        Exit Do
                    End If

                    C.Add ProcName
                    StartLine = .CodeModule.ProcCountLines(ProcName, _
                        vbext_pk_Proc) + StartLine
                Loop
            End With
        Next
    End With
End Sub

Sub Demo()
    Dim C As New Collection
    Dim I As Long
    Dim S As String

    S = ""
    ListMacrosInPresentation ActivePresentation, C
    For I = 1 To C.Count
        S = S + C(I) + ", "
    Next
    MsgBox Left(S, Len(S) - 2)
End Sub

Contact OfficeOne on email at officeone@officeoneonline.com. Copyright © 2001-2023 OfficeOne. All rights reserved.