How do I get a list of Custom Shows in a presentation?
How do I get the list of Slides in a particular Custom Show?

Custom Shows are called NamedSlideShows in PowerPoint Object Model (OM). The NamedSlideShows collection is available through the NamedSlideShows property of SlideShowSettings of the Presentation object. The following code iterates through all the custom shows in a presentation and returns the custom shows and their member slide IDs. You can use FindBySlideID() method of the Slides collection to get hold of Slide object.

Sub GetListofCustomShows(ByVal Pres As Presentation, _
    ByRef CustomShows As Collection)

    Dim NS As NamedSlideShow
    Dim I As Long
    Dim S As String

    With Pres.SlideShowSettings
        For Each NS In .NamedSlideShows
            S = NS.Name + ": "
            For I = 1 To NS.Count
                S = S + CStr(NS.SlideIDs(I)) + ", "
            Next
            S = Left(S, Len(S) - 2)
            CustomShows.Add S
        Next
    End With
End Sub

The following code tests the above code:

Sub Test()
    Dim Msg As String
    Dim CustomShows As Collection
    Dim I As Long

    Set CustomShows = New Collection
    GetListofCustomShows ActivePresentation, CustomShows
    For I = 1 To CustomShows.Count
        Msg = Msg + CustomShows(I) + vbCrLf
    Next
    MsgBox Msg, vbInformation Or vbOKOnly, "Custom Shows List"

    Set CustomShows = Nothing
End Sub

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