Excel VBA Problem when adding an ImageCombo-ActiveX to a worksheet - excel

I'm trying to add an ImageCombo-ActiveX control to an Excel worksheet by using the VBA-function .OLEObjects.Add(classtype:="MSComctlLib.ImageComboCtl.2", Top:=TopPos, Left:=LeftPos, Height:=0, Width:=0).
When doing so, the ImageCombo control is displayed on the worksheet in a preloaded state:
ImageCombo Preloaded State
When doing a check with Winspector Spy, it turned out then the ActiveX-Window is loaded as a child-window of an invisible window within Excel named as 'CtlFrameworkParking':
ActiveX control window
instead of being diplayed as an ImageCombo-control. To force this, I first have to make the worksheet window invisble and then redisplay it:
Status after Re-displaying the worksheet window
Finally, after manually scrolling down a line, the ImageCombo-control is diplayed at the desired location with the desired size.
Status after worksheet scroll
Reinspecting with Winspector Spy the ActiveX-Window now is located within the worksheet window:
final correct status
Is there any way to programatically force the ActiveX-Window to show in final state on the worksheet window, probably with some api calls?

I Solved the problem doing it the dirty way by adding the following lines:
Function ShowLanguageDropDown(TargetSheetName As String, Optional TopPos As Single = 0#, Optional LeftPos As Single = 0#, Optional SetVisible As Boolean = False) As MSComctlLib.ImageCombo
'---------------------------------------------------------------------------------------
' Procedure : ShowLanguageDropDown
' Author : Bernd Birkicht
' Date : 05.11.2022
' Purpose : inserts an image dropdown on the target sheet, requires prelodad OLE-objects on a SourceSheet
' containing the ImageDropdown and the to be associated pre-set ImageList-activeX control
'---------------------------------------------------------------------------------------
'
'........
Set TargetSheet = ActiveWorkbook.Sheets(TargetSheetName)
'........
With TargetSheet
.Visible = xlSheetHidden
.Visible = xlSheetVisible
.Activate
End With
Set TargetSheet = Nothing
CurrentScrollRow = ActiveWindow.ScrollRow
ActiveWindow.ScrollRow = 2
ActiveWindow.ScrollRow = CurrentScrollRow
End function
These commands now do programmatically what I did manually before resulting in now correctly displaying the ImageDropdown control at the desired location on the worksheet.
I would welcome a more elegant solution.

I finally decided to to drop the approach of using an ImageCombo-ActiveX control directly on an Excel worksheet due to i encounterd a big bunch of problems with the ImageCombo-control further on.
When stopping the screen update, the Drop-down arrow within the control occasionally disappears and the control repaints not always fully. I was not able to fix this.
At the end of the day, I used the ImageCombo-ActiveX control within a modeless userform which is not affected at all from application screen updating or events processed by the application while the userform is displayed.
To prevent the userform from floating on the windows screen, I now attached the userform to the Excel-application window and cropped the userform frame around the ImageCombo-control.
Please find below the code:
Private Sub UserForm_Initialize()
'---------------------------------------------------------------------------------------
' Procedure : UserForm_Initialize
' Author : Bernd Birkicht
' Date : 10.11.2022
' Purpose : fills the image-Dropdownbox valid lnaguage entries
'---------------------------------------------------------------------------------------
'
Static BasicInit As Boolean
On Error GoTo UserForm_Initialize_Error
If BasicInit Then Exit Sub 'already initialised?
....
'adapt userform window to Dropbox size
Me.Height = Me!LanguageDropBox.Height
Me.Width = Me!LanguageDropBox.Width
With Me.LanguageDropBox
Set .ImageList = Nothing 'delete image list and import again
If .ImageList Is Nothing Then Set .ImageList = Me.LanguageSmallIconImageList
mlngptrCtlHwnd = .hwnd
.Locked = True
End With
PopulateComboItems Translate:=bTranslate
UserForm_Initialize_Exit:
Crop_UF_Frame
BasicInit = MakeChild(Me)
Exit Sub
UserForm_Initialize_Error:
Select Case Err.Number
Case Else
'MsgBox "Error " & Err.Number & " (" & Err.Description & ") in Prozedur UserForm_Initialize aus Formular LanguageDropBoxForm"
'LogError Err.Number, Err.Description, "in Prozedur UserForm_Initialize aus Formular LanguageDropBoxForm"
ErrEx.CallGlobalErrorHandler ' Call the global error handler to deal with unhandled errors
Resume UserForm_Initialize_Exit:
End Select
End Sub
Private Sub Crop_UF_Frame()
'---------------------------------------------------------------------------------------
' Procedure : Crop_UF_Frame
' Author : Nepumuk https://www.herber.de/forum/archiv/1456to1460/1459854_Userform_komplett_ohne_Rand.html
' Date : 21.11.2015
' Purpose : crop the userform frame
' geändert : 11.11.2022 Bernd Birkicht
' ergänzt: Region eingrenzen auf einzelnes Control in der Userform
'---------------------------------------------------------------------------------------
'
Dim udtRect As RECT, udtPoint As POINTAPI
Dim lngptrStyle As LongPtr, lngptrRegion As LongPtr, lngParenthWnd As LongPtr
Static BasicInit As Boolean
On Error GoTo Crop_UF_Frame_Error
mlngptrHwnd = FindWindowA(GC_CLASSNAMEMSFORM, Caption)
lngptrStyle = GetWindowLongA(mlngptrHwnd, GWL_STYLE)
Call SetWindowLongA(mlngptrHwnd, GWL_STYLE, lngptrStyle And Not WS_CAPTION)
Call DrawMenuBar(mlngptrHwnd)
Call GetWindowRect(mlngptrHwnd, udtRect)
udtPoint.x = udtRect.right
udtPoint.y = udtRect.bottom
Call ScreenToClient(mlngptrHwnd, udtPoint)
'11.11.2022 set region
If mlngptrCtlHwnd = 0 Then 'Control in Userform gewählt?
'remove userform frame
With udtRect
.bottom = udtPoint.y
.left = 4
.right = udtPoint.x
.top = 4
End With
Else
'set region to WindowRect of the selected control
Call GetWindowRect(mlngptrCtlHwnd, udtRect)
End If
lngptrRegion = CreateRectRgnIndirect(udtRect)
Call SetWindowRgn(mlngptrHwnd, lngptrRegion, 1&)
Crop_UF_Frame_Exit:
Exit Sub
Crop_UF_Frame_Error:
Select Case Err.Number
Case Else
ErrEx.CallGlobalErrorHandler ' Call the global error handler to deal with unhandled errors
Resume Crop_UF_Frame_Exit:
End Select
End Sub
Private Function MakeChild(ByVal UF As UserForm) As Boolean
Dim DeskHWnd As LongPtr
Dim WindowHWnd As LongPtr
Dim UFhWnd As LongPtr
MakeChild = False
' get the window handle of the Excel desktop
DeskHWnd = FindWindowEx(Application.hwnd, 0&, "XLDESK", vbNullString)
If DeskHWnd > 0 Then
' get the window handle of the ActiveWindow
WindowHWnd = FindWindowEx(DeskHWnd, 0&, "EXCEL7", ActiveWindow.Caption)
If WindowHWnd > 0 Then
' ok
Else
MsgBox "Unable to get the window handle of the ActiveWindow."
Exit Function
End If
Else
MsgBox "Unable to get the window handle of the Excel Desktop."
Exit Function
End If
' get the window handle of the userform
Call IUnknown_GetWindow(UF, VarPtr(UFhWnd))
mlngptrOldParenthWnd = GetParent(UFhWnd)
If mlngptrOldParenthWnd = WindowHWnd Then Exit Function 'Assignment to Excel window already done
'make the userform a child window of the MDIForm
If (UFhWnd > 0) And (WindowHWnd > 0) Then
' make the userform a child window of the ActiveWindow
If SetParent(UFhWnd, WindowHWnd) = 0 Then
''''''''''''''''''''
' an error occurred.
''''''''''''''''''''
MsgBox "The call to SetParent failed."
Exit Function
End If
End If
MakeChild = True
End Function
call:
If Wb.ActiveSheet.Name = Translate_To_OriginalText(InitSheetName) And LanguageDropBoxUForm Is Nothing Then
LanguageDropBoxForm.Hide 'Lädt das Window ohne es anzuzeigen
If UserForms.count > 0 Then Set LanguageDropBoxUForm = UserForms(UserForms.count - 1)
LanguageDropBoxForm.Move 660#, 85#
LanguageDropBoxForm.Show vbModeless 'show Language-Select-Window modeless
endif

Related

How To Close a UserForm Properly in Excel VBA?

I need to close a UserForm from a procedure that is inside the general module. The following code is just a test. I cannot use Me once that I am out of the form module.
Private Sub btnCancel_Click()
On Error GoTo TreatError
Dim screen As Object
Set screen = UserForms.Add(Me.Name)
Unload screen
Leave:
Set screen = Nothing
Exit Sub
TreatError:
GoTo Leave
End Sub
What's missing in this code? When I press the Cancel button, nothing happens, well, the form still keeps loaded. This UserForm is ShowModal True.
thanks in advance.
Ok Pᴇʜ. Here you are:
Public Sub EditarCombo(nomeColuna As String, itemCombobox As Variant, novoValor As Variant)
On Error GoTo TratarErro
Dim planilha As Worksheet
Dim planRamais As Worksheet
Dim tela As UserForm
If ((itemCombobox & "") <> "") Then
If ((Trim(novoValor) & "") <> "") Then
If (itemCombobox <> Trim(novoValor)) Then
Set planilha = Worksheets("CombosRamais")
Set planRamais = Worksheets("Ramais")
EditarNaColuna planilha, nomeColuna, itemCombobox, novoValor
ExcluirDuplicadasNaColuna planilha, nomeColuna, novoValor
OrdemarColuna planilha, nomeColuna, True
RedefinirAreaColuna planilha, planRamais, nomeColuna
EditarNaColuna planRamais, nomeColuna, itemCombobox, novoValor
Else
MsgBox "Você deve digitar um novo valor para o item escolhido.", vbInformation + vbOKOnly, "Editar Item"
GoTo Sair
End If
Else
MsgBox "O campo de novo valor está vazio.", vbInformation + vbOKOnly, "Editar Item"
GoTo Sair
End If
Else
MsgBox "Escolha um item na lista para ser editado.", vbInformation + vbOKOnly, "Editar Item"
GoTo Sair
End If
Set tela = UserForms.Add(Replace(nomeColuna, "Col", "frmEditar"))
Unload tela
Sair:
Set tela = Nothing
Set planilha = Nothing
Set planRamais = Nothing
Exit Sub
TratarErro:
GoTo Sair
End Sub
Based on your comment to FunThomas' answer you would like to have a function like that
Public Function UnLoadFrm(formName As String)
Dim frm As Object
For Each frm In VBA.UserForms
If frm.Name = formName Then
Unload frm
Exit Function
End If
Next frm
End Function
Be careful when using it as it is case sensitive. It might also be a good idea to use frm.Hide instead of Unload frm but then you should also rename the function.
Don't unload forms - just hide them.
From the form itself, use Me.Hide.
If you want to hide the form within module code, use UserForm1.Hide.
Destroying a form, especially in the wrong moment, can lead to surprising behavior that is really hard to understand. If you want to know more, read about "Default Instances". Hiding a form simply hides it from the screen so that it is not visible for the moment, but stays in memory.
Update
My answer was mainly to point out that you shoudn't destroy a form. If the subroutine is called from different forms and you pass the control (eg comboBox) as parameter, you can use the Parent-property to get the form object and hide it:
Public Sub EditarCombo(nomeColuna As String, itemCombobox As Control, novoValor As Variant)
(...)
itemCombobox.Parent.Hide
(...)
End Sub

Glitch when using RefEdit_Change Event in a VBA UserForm

The following should happen:
1. UserForm with 2 RefEdit controls is shown
2. The first RefEdit is used to select a range
3. The RefEdit_Change event adjusts the second RefEdit control to .offset(0,1) of the range
Here my code until now:
Module1:
Dim frmSelectXY As New frmSelectImportData
With frmSelectXY
.Show
.DoStuffWithTheSelectedRanges
End With
UserForm: frmSelectImportData
Option Explicit
Private Type TView
IsCancelled As Boolean
xrng As Range
yrng As Range
End Type
Private this As TView
Public Property Get IsCancelled() As Boolean
IsCancelled = this.IsCancelled
End Property
Public Property Get yrng() As Range
Set yrng = this.yrng
End Property
Public Property Get xrng() As Range
Set xrng = this.xrng
End Property
'Here is where the fun happens
Private Sub RefEdit1_Change()
'RefEdit2.Value = RefEdit1.Value
If InStr(1, RefEdit1.Value, "[") <> 0 And InStr(1, RefEdit1.Value, "!") <> 0 Then
RefEdit2.Value = Range(RefEdit1.Value).offset(0, 1).Address(External:=True)
ElseIf InStr(1, RefEdit1.Value, "!") <> 0 Then
RefEdit2.Value = Range(RefEdit1.Value).offset(0, 1).Parent.Name & "!" & Range(RefEdit1.Value).offset(0, 1).Address(External:=False)
Else
RefEdit2.Value = Range(RefEdit1.Value).offset(0, 1).Address(External:=False)
End If
End Sub
Private Sub SaveBTN_Click()
Set this.xrng = Range(RefEdit1.Value)
Set this.yrng = Range(RefEdit2.Value)
If Not validate Then
MsgBox "x-values and y-values need to have the same size."
Else
Me.Hide
End If
End Sub
Function validate() As Boolean
validate = False
If this.xrng.count = this.yrng.count Then validate = True
End Function
RefEdit1_Change should adjust the value of RefEdit2 such that it will show the reference to the column just next to it or better .offest(0,1) to it.
But that isn't what happens.. the value doesn't get changed. As soon as the User clicks into RefEdit2 if RefEdit1 has already been changed, the program aborts without error message. If you Cancle the UserForm I have also experienced hard crashes of excel. I have temporarily fixed the problem by rebuilding the UserForm from scratch and renaming the RefEdits. But at some point it reapeared. It seems as if it is an Excel/VBA inherent problem.
Does anybody know how to fix this?
Ugly hacks and workarounds are welcome, anything is better than, abort without error message.
you need to enclose Range(RefEdit1.Value).offset(0, 1).Parent.Name in ' so
="'" & Range(RefEdit1.Value).offset(0, 1).Parent.Name & "'!"

Pivot Chart Title to Display Multiple Selected Items

I have a pivotchart that when the selected filter (work center) is changed, it updates the chart title to display that work center name. However, if I check the box to allow multiple selections, the chart title simply shows "All" instead of showing each of the actual selected items. I haven't found a way to get it to show what I'm looking for. Below is the code that I'm using to update the chart title as well as the code for the filter change event that fires it off
Option Explicit
Private Sub Worksheet_PivotTableUpdate(ByVal Target As PivotTable)
On Error Resume Next
Application.Run "'Prod_Tools.xlam'!gPTWCChange", Target.PivotFields("WorkCenter").CurrentPage
On Error GoTo 0
End Sub
Sub gPTWCChange(ByVal WC As String)
Dim wb1 As Workbook
Dim CPWB1 As Workbook
For Each wb1 In Workbooks
If InStr(1, wb1.Name, "Capacity Planning Rep", vbTextCompare) > 0 Then
Set CPWB1 = Workbooks(wb1.Name)
Exit For
End If
Next wb1
On Error Resume Next
CPWB1.Charts("Workcenter By Week").ChartTitle.Text = "Work Center: " & WC
On Error GoTo 0
End Sub
What I would like is when multiple items are selected, have the chart title look like "Data for: Workcenter_A, Workcenter_B, Workcenter_F"
Here's your adapted sub. Notice that its parameter has changed.
Public Sub gPTWCChange(ByVal pfWC As Excel.PivotField)
Const sSEPARATOR As String = ", "
Dim sChartTitle As String
Dim oPivotItem As Excel.PivotItem
Dim lVisibleCount As Long
'... Your original code ...
Dim wb1 As Workbook
Dim CPWB1 As Workbook
For Each wb1 In Workbooks
If InStr(1, wb1.Name, "Capacity Planning Rep", vbTextCompare) > 0 Then
Set CPWB1 = Workbooks(wb1.Name)
Exit For
End If
Next wb1
'... New code to compute the chart title ...
If pfWC.EnableMultiplePageItems Then
'Build the chart title from the visible items in the PivotField.
lVisibleCount = 0
For Each oPivotItem In pfWC.PivotItems
If oPivotItem.Visible Then
lVisibleCount = lVisibleCount + 1
sChartTitle = sChartTitle & sSEPARATOR & oPivotItem.Caption
End If
Next
'Drop the leading separator.
sChartTitle = Mid$(sChartTitle, Len(sSEPARATOR) + 1)
'Manage plural.
sChartTitle = "Work Center" & IIf(lVisibleCount > 1, "s", "") & ": " & sChartTitle
Else
sChartTitle = "Work Center: " & pfWC.CurrentPage
End If
'... Your original code ...
On Error Resume Next
CPWB1.Charts("Workcenter By Week").ChartTitle.Text = sChartTitle
On Error GoTo 0
End Sub
And call your sub as follows:
Application.Run "'Prod_Tools.xlam'!gPTWCChange", Target.PivotFields("WorkCenter")
The principle is to send your sub a reference to the PivotField object, and from there, check its EnableMultiplePageItems property.

What is the cause of Invalid use of null error 94 in a MouseMove event handler in Excel

I have a mousemove event handler attached to a 3-column listbox called lstUneditedStudents in an Excel UserForm. The bound column is number 1. The column contains alphanumeric strings like this "A202H". Why am I getting an Invalid use of Null in this code? (ErrorLog is my own class which logs errors to a worksheet. That's working smoothly, documenting my errors as I debug.)
Private Sub lstUneditedStudents_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
On Error Resume Next
If Button = 1 Then
Dim dob As DataObject, listValue As String
listValue = lstUneditedStudents.value
If listValue <> "" Then
Set dob = New DataObject
dob.SetText listValue
dob.StartDrag
End If
End If
If Err.Number <> 0 Then
Dim errLog As New ErrorLog
errLog.Log "frmEditClasses", "lstUneditedStudents_MouseMove", Err.Source, Err.Description, Err.Number
End If
End Sub
When you click on the listbox, there is an annoying delay and then the listbox goes blank before re-populating. Once you let this settle down, the drag works and other subroutines handle the move from this listbox to another listbox. However, this error is still raised.
I think you just need to check if lstUneditedStudents.value is null before assigning it to a variable. For example:
Private Sub lstUneditedStudents_MouseMove(ByVal Button As Integer, ByVal Shift As Integer, ByVal X As Single, ByVal Y As Single)
On Error Resume Next
If Button = 1 Then
Dim dob As DataObject, listValue As String
If Not IsNull(lstUneditedStudents.value) Then
listValue = lstUneditedStudents.value
If listValue <> "" Then
Set dob = New DataObject
dob.SetText listValue
dob.StartDrag
End If
End If
End If
If Err.Number <> 0 Then
Dim errLog As New ErrorLog
errLog.Log "frmEditClasses", "lstUneditedStudents_MouseMove", Err.Source, Err.Description, Err.Number
End If
End Sub

Powerpoint: Manually set Slide Name

Context:
A PowerPoint slide in C# has a property Slide.Name (usually contains an arbitrary string value).
In my C# application I would like to use this property to identify slides (the slide order is to unreliable).
Question:
How can I manually set the Slide.Name property in the PowerPoint Application?
My problem is very like to the: “How to name an object within a PowerPoint slide?” but just on the slide level.
Any help would be appreciated.
There is no built-in functionality in PowerPoint that allows you to edit the name of a slide. As Steve mentioned, you have to do it using VBA code. The slide name will never change due to inserting more slides, and it will stay the same even if you close PowerPoint; the slide name set in VBA code is persistent. Here's some code I wrote to allow you to easily view the name of the currently selected slide and allow you to rename it:
'------------------------------------------------------------------
' NameSlide()
'
' Renames the current slide so you can refer to this slide in
' VBA by name. This is not used as part of the application;
' it is for maintenance and for use only by developers of
' the PowerPoint presentation.
'
' 1. In Normal view, click on the slide you wish to rename
' 2. ALT+F11 to VB Editor
' 3. F5 to run this subroutine
'------------------------------------------------------------------
Sub NameSlide()
Dim curName As String
curName = Application.ActiveWindow.View.Slide.name
Dim newName As String
retry:
newName = InputBox("Enter the new name for slide '" + curName + "', or press Cancel to keep existing name.", "Rename slide")
If Trim(newName) = "" Then Exit Sub
Dim s As Slide
' check if this slide name already exists
On Error GoTo SlideNotFound
Set s = ActivePresentation.Slides(newName)
On Error GoTo 0
MsgBox "Slide with this name already exists!"
GoTo retry
Exit Sub
SlideNotFound:
On Error GoTo 0
Application.ActiveWindow.View.Slide.name = newName
MsgBox "Slide renamed to '" + newName + "'."
End Sub
You can't manually set the slide name, but with a bit of code, it's simple. In VBA, for example:
Sub NameThatSlide()
ActivePresentation.Slides(1).Name = "Whatever You Like Here"
End Sub
You can rename a slide manually or with VBA. Once you know how, the door opens to some interesting possibilities, which I will demonstrate with code below.
Manually renaming slides. This ability is hidden in the VBA Editor's Properties pane, but it does not require coding.
If the Developer ribbon is not visible, enable it: File > Options > Customize Ribbon > check the Developer Main Tab.
From the Developer ribbon, click the Visual Basic menu item to open the Visual Basic Editor.
Press the Ctrl+R keys to navigate to the Project Explorer pane.
Expand "Microsoft PowerPoint Objects"
Click on any slide to select it.
Press the F4 key to navigate to the Properties pane.
Edit the (Name) item, and press Enter to apply the name change.
The slide name change may not appear immediately in the VBA Project Explorer pane. As long as the name is correct in the Properties pane, the name changed successfully.
This VBA code will also do the trick (hide slide number 1):
ActivePresentation.Slides(1).SlideShowTransition.Hidden = msoTrue
This code block covers a few ways to manage slide names and answers the main question.
Option Explicit
Public Function RenameSlide(oldName As String, newName As String)
' RenameSlide finds slide oldName and renames it to newName.
' Arguements:
' oldName: current (old) name of existing slide
' newName: new name for slide.
'
Dim tempBool As Boolean
Dim sld As Slide
Dim RetVal(0 To 1) As String
' Check if oldName can be found.
If SlideExists(oldName) Then
Set sld = Application.ActivePresentation.Slides(oldName)
Else
RetVal(0) = 1 'Error 1
RetVal(1) = "Error 1: slide with name " & oldName & " not found. Aborting."
Exit Function
End If
' Check if this slide name newName already exists.
If SlideExists(newName) Then
RetVal(0) = 2 'Error 1
RetVal(1) = "Error 2: slide with name " & newName & " already exists. Aborting."
Exit Function
End If
' Rename the slide
'Application.ActivePresentation.Slides(oldName) = newName
Application.ActivePresentation.Slides(oldName).Select
Application.ActiveWindow.View.Slide.Name = newName 'current slide
RetVal(0) = 0 'Success
RetVal(1) = "Success: slide renamed from '" & oldName & "' to '" & newName & "'."
End Function
Public Sub SetSlideName()
' Prompt user for new name for active slide.
'
Dim oldName As String
Dim newName As String
Dim sld As Slide
Dim msg As String
' Get current name of active slide.
oldName = Application.ActiveWindow.View.Slide.Name
msg = "Enter the new name for slide '" + oldName + "'."
retry:
newName = ""
' Prompt for new slide name. Loop until a name of at least 1 character is provided.
Do While newName = ""
newName = InputBox(msg, "Rename slide")
newName = Trim(newName)
If Len(newName) = 0 Then
msg = "Try again. You must enter a slide name to continue."
ElseIf newName = oldName Or newName = Str(vbCancel) Then
Exit Sub
End If
Loop
' If an existing slide already has name newName, then
' go back and prompt user again.slide name already exists
If SlideExists(newName) Then
msg = "Slide with this name already exists!"
GoTo retry
End If
' Set the new slide name
Application.ActiveWindow.View.Slide.Name = newName
MsgBox "Slide renamed to '" + newName + "'."
End Sub
Public Function SlideExists(SlideName As String) As Boolean
Dim RetVal As Boolean
Dim sld
' Assume slide does not exist.
SlideExists = False
' Try to find slide by name.
' If we error out, the slide does NOT exist.
On Error GoTo NoSlide
Set sld = ActivePresentation.Slides(SlideName)
' If we got this far, the slide DOES exist.
SlideExists = True
Exit Function
NoSlide:
' Error setting slide objects shows
' that slides does NOT exist.
SlideExists = False
End Function
As an aside, I use the slide naming trick and a little VBA to selectively remove certain slides from printing. I added a few extra VBA macros for the sake of populating the Macros list. From any slide: Developer ribbon > Macros > Select Macro > Run button. Use this method to kick off my PresentSlide, DontPresentSlide, PrintSlide and DontPrintSlide macros. Once you have properly tagged your various slides, simply run the PrepToPresentSlides or PrepToPrintSlides macro before you present or print, respectively.
Play around with these macros a bit and read the comments. You will find that I wrote the code extensibly, so you can modify it easily for your needs.
The code below helps me to manage which slides and objects are printed and which are presented on-screen. This is particularly useful when I want to print reference slides but not cover them. It is even more useful when I have slides with animations. Animations don't usually translate print well. So, I choose not to print some animated objects at all. In fact, I can even add in substitute content for the objects to be used just for printing (hidden when presenting) - though I rarely do this. Instead, I will typically hide the animation from printing or create a slide to present and a non-animated copy of it for print. With these macros, it is easy to manage a mix and match of slides and objects for print and slides and objects for presentation. I hope you enjoy.
Option Explicit
' DontPresentSlide - run macro while on a slide you wish to skip while presenting.
' The slide name will be appended with "NoPresent". You still
' need to run PrepToPresent before presenting to hide slide.
' PresentSlide - "NoPresent" will be removed from the slide. You still
' need to run PrepToPresent before presenting to hide slide.
' PrepToPesentSlides() - Unhide slides and objects you want presented and
' hide slides and objects you do NOT want presented.
' ShowNoPressnt() - show slides and shapes marked "NoPresent"
' HideNoPresent() - hide slides and shapes marked "NoPresent"
' DontPrintSlide - run macro while on a slide you wish to skip while presenting.
' The slide name will be appended with "NoPrint". You still
' need to run PrepToPresent before presenting to hide slide.
' PrintSlide - "NoPrint" will be removed from the slide. You still
' need to run PrepToPresent before presenting to hide slide.
' PrepToPrintSlides() - Unhide slides and objects you want printed and
' hide slides and objects you do NOT want printed.
' ShowNoPrint() - show slides and shapes marked "NoPrint"
' HideNoPrint() - hide slides and shapes marked "NoPrint"
' ShowHideSlides() - Hide or Unhide slides based on slide name.
' ShowHideShapes() - Hide or Unhide shapes based on shapes name.
Public Const cjaHide = False
Public Const cjaShow = True
Public Const cjaToggle = 2
Sub ShowHideSlides(NameContains As String _
, Optional LMR As String = "R" _
, Optional ShowSlide As Integer = False)
' Show or Hide slides based on slide name.
' Arguements:
' NameContains (string):
' slides with this string will be modified.
' LMR (string): enter L, M or R to indicate
' searching the Left, Middle or Right of
' the slide name, respectively.
' ShowSlide (integer):
' Show: True (-1)
' Hide: False (0)
' Toggle: 2
'
' To show or hide slides manually:
' Right-click the slide thumbnail, then click Hide Slide
' To rename slides,
' Use this VBA: ActiveWindow.View.Slide.Name = "NewSlideName"
' Or, edit the (Name) property in the VBA Properties window.
'
Dim sldCurrent As Slide
Dim found As Boolean
found = False
LMR = Trim(UCase(LMR))
If LMR <> "L" And LMR <> "M" Then LMR = "R"
'Loop through each slide in presentation.
For Each sldCurrent In ActivePresentation.Slides
'Match shape name left, right or middle as per LMR arguement.
'ActiveWindow.View.Slide.Name or Slide.SlideNumber
found = False
If LMR = "R" And LCase(right(sldCurrent.Name, Len(NameContains))) = LCase(NameContains) Then
found = True
ElseIf LMR = "L" And LCase(left(sldCurrent.Name, Len(NameContains))) = LCase(NameContains) Then
found = True
ElseIf LMR = "M" And InStr(1, LCase(NameContains), LCase(sldCurrent.Name)) Then
found = True
End If
'If match found, then set shape visibility per ShowShape arguement.
If found Then
If ShowSlide = True Then
ActivePresentation.Slides(sldCurrent.SlideNumber).SlideShowTransition.Hidden = msoFalse
ElseIf ShowSlide = False Then
ActivePresentation.Slides(sldCurrent.SlideNumber).SlideShowTransition.Hidden = msoTrue
Else
ActivePresentation.Slides(sldCurrent.SlideNumber).SlideShowTransition.Hidden = Not ActivePresentation.Slides(sldCurrent.SlideNumber).SlideShowTransition.Hidden
End If
End If
Next 'sldCurrent
End Sub
Sub ShowHideShapes(NameContains As String _
, Optional LMR As String = "R" _
, Optional ShowShape As Integer = False)
' Show or Hide shapes/objects based on object name.
' Arguements:
' NameContains (string):
' shapes with this string will be modified.
' LMR (string): enter L, M or R to indicate
' searching the Left, Middle or Right of
' the slide name, respectively.
' ShowSlide (integer):
' Show: True (-1)
' Hide: False (0)
' Toggle: 2
'
' To show, hide and/or rename objects:
' 1. Turn on Selection Pane via: Home Ribbon >
' Select > Selection Pane.
' 2. Double-click a shape name to rename it.
' 3. Click the eye icon to the far right to show/hide a shape.
Dim shpCurrent As Shape
Dim sldCurrent As Slide
Dim found As Boolean
found = False
LMR = Trim(UCase(LMR))
If LMR <> "L" And LMR <> "M" Then LMR = "R"
'Loop through each slide in presentation.
For Each sldCurrent In ActivePresentation.Slides
With sldCurrent
'Loop through each shape on current slide.
For Each shpCurrent In .Shapes
'Match shape name left, right or middle as per LMR arguement.
found = False
If LMR = "R" And right(shpCurrent.Name, Len(NameContains)) = NameContains Then
found = True
ElseIf LMR = "L" And left(shpCurrent.Name, Len(NameContains)) = NameContains Then
found = True
ElseIf LMR = "M" And InStr(1, NameContains, shpCurrent.Name) Then
found = True
End If
'If match found, then set shape visibility per ShowShape arguement.
If found Then
If ShowShape = True Then
shpCurrent.Visible = True
ElseIf ShowShape = False Then
shpCurrent.Visible = False
Else
shpCurrent.Visible = Not shpCurrent.Visible
End If
End If
Next 'sldCurrent
End With 'sldCurrent
Next 'sldCurrent
End Sub
Sub HideNoPrint()
' Hide slides and shapes you do NOT want printed.
'
' Run this macro to hide all slides and shapes that
' end with the string "NoPrint".
' Usage. Assume you have slides that contain animations that
' make the printed slide difficult or impossible to read.
' Let's further suppose you plan to present certain slides
' but not print them.
' 1. Add the"NoPrint" suffix to any shapes that clutter
' the printed page.
' 2. Add the "NoPrint" suffix to slides you don't want to
' print.
' 3. Run this macro to hide shapes and slides.
' 4. Print the slides.
' 5. Optionally, run the ShowNoPrint() macro in preparation
' for presenting the slides.
ShowHideShapes "NoPrint", "R", False
ShowHideSlides "NoPrint", "R", False
End Sub
Sub ShowNoPrint()
' Unhide slides and shapes that were hidden
' to prevent them from being printed in handouts.
'
ShowHideShapes "NoPrint", "P", True
ShowHideSlides "NoPrint", "P", True
End Sub
Sub HideNoPressent()
' Hide objects you do NOT want to present on screen.
'
' Run this macro to hide all slides and shapes that
' end with the string "NoPresent".
'
' Usage. Assume you have slides that contain supporting material
' that you wish to provide as printed handouts but not show.
' You can manually hide those slides and objects of course. I
' prefer to use these macros.
' 1. Add the"NoPresent" suffix to any shapes that you want
' to print to handouts but not show on-screen.
' 2. Add the "NoPresent" suffix to slides you want to
' print but not display on screen, such as reference slides.
' 3. Run this macro to hide the "NoPresent" shapes and slides.
' 4. Present your slides.
' 5. Optionally, run the ShowNoPresent() macro in preparation
' for printing the slides.
'
ShowHideShapes "NoPressent", "R", False
ShowHideSlides "NoPressent", "R", False
End Sub
Sub ShowNoPresent()
' Unhide objects that were hidden to prevent them from
' being presented on screen.
'
ShowHideShapes "NoPressent", "P", True
ShowHideSlides "NoPressent", "P", True
End Sub
Sub PrepToPrintSlides()
' Unhide objects you want printed and
' hide objects you do NOT want printed.
ShowNoPresent
HideNoPrint
End Sub
Sub PrepToPresentSlides()
' Unhide objects you want presented and
' hide objects you do NOT want presented.
ShowNoPrint
HideNoPresent
End Sub
Sub DontPresentSlide()
Dim RetVal, sldName As String
sldName = Application.ActiveWindow.View.Slide.Name
If InStr(1, sldName, "NoPresent", vbBinaryCompare) = 0 Then
RetVal = RenameSlide(sldName, sldName & "-NoPresent")
End If
HideNoPresent
End Sub
Sub PresentSlide()
Dim RetVal, sldName As String, strStart As String, newName As String
'Remove the NoPresent suffix from the current slide.
'get slide name
sldName = Application.ActiveWindow.View.Slide.Name
'Unhide slide
ActivePresentation.Slides(sldName).SlideShowTransition.Hidden = msoFalse
'remove "-NoPresent" from slide name
Do
strStart = InStr(1, sldName, "-NoPresent")
If InStr(1, sldName, "-NoPresent") Then
newName = left(sldName, strStart - 1) & right(sldName, Len(sldName) - strStart - 9)
RetVal = RenameSlide(sldName, newName)
End If
sldName = Application.ActiveWindow.View.Slide.Name
Loop Until InStr(1, sldName, "-NoPresent") = 0
'remove "NoPresent" from slide name
Do
strStart = InStr(1, sldName, "NoPresent")
If InStr(1, sldName, "NoPresent") Then
newName = left(sldName, strStart - 1) & right(sldName, Len(sldName) - strStart - 8)
RetVal = RenameSlide(sldName, newName)
End If
sldName = Application.ActiveWindow.View.Slide.Name
Loop Until InStr(1, sldName, "NoPresent") = 0
End Sub
Sub DontPrintSlide()
Dim RetVal, sldName As String
sldName = Application.ActiveWindow.View.Slide.Name
If InStr(1, sldName, "NoPrint", vbBinaryCompare) = 0 Then
RetVal = RenameSlide(sldName, sldName & "-NoPrint")
End If
HideNoPrint
End Sub
Sub PrintSlide()
Dim RetVal, sldName As String, strStart As String, newName As String
'Remove the NoPrint suffix from the current slide.
'get slide name
sldName = Application.ActiveWindow.View.Slide.Name
'Unhide slide
ActivePresentation.Slides(sldName).SlideShowTransition.Hidden = msoFalse
'remove "-NoPrint" from slide name
Do
strStart = InStr(1, sldName, "-NoPrint")
If InStr(1, sldName, "-NoPrint") Then
newName = left(sldName, strStart - 1) & right(sldName, Len(sldName) - strStart - 7)
RetVal = RenameSlide(sldName, newName)
End If
sldName = Application.ActiveWindow.View.Slide.Name
Loop Until InStr(1, sldName, "-NoPrint") = 0
'remove "NoPrint" from slide name
Do
strStart = InStr(1, sldName, "NoPrint")
If InStr(1, sldName, "NoPrint") Then
newName = left(sldName, strStart - 1) & right(sldName, Len(sldName) - strStart - 6)
RetVal = RenameSlide(sldName, newName)
End If
sldName = Application.ActiveWindow.View.Slide.Name
Loop Until InStr(1, sldName, "NoPrint") = 0
End Sub
Sub HideAllCovers()
' Run this macro to hide all Covers.
ShowHideShapes "Cover", "L", False
End Sub
Sub ShowAllCovers()
' Run this macro to hide all Covers.
ShowHideShapes "Cover", "L", True
End Sub
Sub HideAllAnswers()
' Run this macro to hide all Covers.
ShowHideShapes "Answer", "L", False
End Sub
Sub ShowAllAnswers()
' Run this macro to hide all Covers.
ShowHideShapes "Answer", "L", True
End Sub
Sub HideAllQuestions()
' Run this macro to hide all Covers.
ShowHideShapes "Question", "L", False
End Sub
Sub ShowAllQuestions()
' Run this macro to hide all Covers.
ShowHideShapes "Question", "L", True
End Sub
Sub ShowAll()
' Run this macro to hide all shapes (Covers and Answers).
ShowAllQuestions
ShowAllAnswers
ShowAllCovers
ShowNoPrint
End Sub
Sub HideAll()
' Run this macro to hide all shapes (Covers and Answers).
HideAllQuestions
HideAllAnswers
HideAllCovers
HideNoPrint
End Sub
Enable the "Developer" tab in "File -> Options -> Customize Ribbon" (Details: https://www.addintools.com/documents/powerpoint/where-is-developer-tab.html)
In the developer tab, follow these steps and see the image below (in Portuguese, sorry)
Enter the developer tab
Select the target slide
If you don't have any active X control (buttons, textboxes, etc.) in the slide, add a dummy button from the developer tab
Select this button on the slide and click "properties" at the developer tab
At the top of the properties window, there is a combo box where you can select the slide instead of the button
Select the slide and see its programming properties, including name
I'm not certain that this will enable you to set the Slide.Name property because I'm not a VBA programmer, but anyway AFAIK the easiest way to name slides in PowerPoint 2010 is using Outline view.
If you position your mouse farthest left on a created slide, you can drag rightwards a kind of vertical slide sorter. At the top of that pane, you'll see two tabs: Slides and Outline.
Select Outline, you'll see each slide numbered and a grey grab button which allows you to reorder your slides. If you click to the right of that, you can type in whatever name you like, say Home.
In the main view pane, the slide will then have Home emblazoned across it. You can then either leave it there, or conceal it by altering the font colour to the background or by moving the text outside the presentation frame.
BTW You can use these names in hyperlinks.
used the Sub SplitFile() function to create individual slides from a deck of >100 slides. All went well!! But can anyone tell me what code do I use to rename the file automatically, assuming that each slide has a title in a text box? I want the slide title to be the file name for the new, individual slide created.
Here's the code I used to create individual slides (as individual files), thanks to whoever posted it online.
Sub SplitFile()
Dim lSlidesPerFile As Long
Dim lTotalSlides As Long
Dim oSourcePres As Presentation
Dim otargetPres As Presentation
Dim sFolder As String
Dim sExt As String
Dim sBaseName As String
Dim lCounter As Long
Dim lPresentationsCount As Long ' how many will we split it into
Dim x As Long
Dim lWindowStart As Long
Dim lWindowEnd As Long
Dim sSplitPresName As String
On Error GoTo ErrorHandler
Set oSourcePres = ActivePresentation
If Not oSourcePres.Saved Then
MsgBox "Please save your presentation then try again"
Exit Sub
End If
lSlidesPerFile = CLng(InputBox("How many slides per file?", "Split Presentation"))
lTotalSlides = oSourcePres.Slides.Count
sFolder = ActivePresentation.Path & "\"
sExt = Mid$(ActivePresentation.Name, InStr(ActivePresentation.Name, ".") + 1)
sBaseName = Mid$(ActivePresentation.Name, 1, InStr(ActivePresentation.Name, ".") - 1)
If (lTotalSlides / lSlidesPerFile) - (lTotalSlides \ lSlidesPerFile) > 0 Then
lPresentationsCount = lTotalSlides \ lSlidesPerFile + 1
Else
lPresentationsCount = lTotalSlides \ lSlidesPerFile
End If
If Not lTotalSlides > lSlidesPerFile Then
MsgBox "There are fewer than " & CStr(lSlidesPerFile) & " slides in this presentation."
Exit Sub
End If
For lCounter = 1 To lPresentationsCount
' which slides will we leave in the presentation?
lWindowEnd = lSlidesPerFile * lCounter
If lWindowEnd > oSourcePres.Slides.Count Then
' odd number of leftover slides in last presentation
lWindowEnd = oSourcePres.Slides.Count
lWindowStart = ((oSourcePres.Slides.Count \ lSlidesPerFile) * lSlidesPerFile) + 1
Else
lWindowStart = lWindowEnd - lSlidesPerFile + 1
End If
' Make a copy of the presentation and open it
For Each oSlide In ActiveWindow.Presentation.Slides
strTitles = strTitles _
& "Slide: " _
& CStr(oSlide.SlideIndex) & vbCrLf _
& oSlide.Shapes.Title.TextFrame.TextRange.Text _
& vbCrLf & vbCrLf
Next oSlide
On Error GoTo ErrorHandler
intFileNum = FreeFile
sSplitPresName = sFolder & sBaseName & _
"_" & CStr(lWindowStart) & "-" & CStr(lWindowEnd) & "." & sExt
oSourcePres.SaveCopyAs sSplitPresName, ppSaveAsDefault
Set otargetPres = Presentations.Open(sSplitPresName, , , True)
With otargetPres
For x = .Slides.Count To lWindowEnd + 1 Step -1
.Slides(x).Delete
Next
For x = lWindowStart - 1 To 1 Step -1
.Slides(x).Delete
Next
.Save
.Close
End With
Next ' lpresentationscount
NormalExit:
Exit Sub
ErrorHandler:
MsgBox "Error encountered"
Resume NormalExit
End Sub

Resources