Hi Eric.
This is working code that I pulled out of one of my apps. This should be everything you need.
You should call HideUsersMenuBars & BuildCustomToolbar when you open the workbook and call RemoveCustomToolBar & RestoreUsersMenuBars when the workbook gets closed.
Sub HideUsersMenuBars()
Dim cBar As CommandBar
'Makes the Main Menu Bar Not Visible
Application.CommandBars("Worksheet Menu Bar").Enabled = False
'Writes the name of the users current menu bars to sheet1, they will be used later in the RestoreUsersMenuBars procedure
'Hide all MenuBars.
Sheet1.Activate
Range("A1").Select
For Each cBar In Application.CommandBars
If cBar.Visible And cBar.Type <> msoBarTypeMenuBar Then
ActiveCell.Value = cBar.Name
cBar.Visible = False
ActiveCell.Offset(1, 0).Select
End If
Next cBar
End Sub
Private Sub BuildCustomToolbar()
Dim NewBar As CommandBar
Dim LastRow As Integer
'Sets NewBar variable to the custom commandbar; sets commandbar icons to top,
'and locks commandbar in position to prevent movement
Set NewBar = CommandBars.Add(Name:="MyCommandBar")
NewBar.Position = msoBarTop
NewBar.Protection = msoBarNoMove
'You can add additional buttons here
With NewBar.Controls
With .Add(msoControlButton)
.Caption = "Home"
.FaceId = 41
.OnAction = "Home"
.Style = msoButtonIconAndCaption
End With
With .Add(msoControlButton)
.Caption = "Exit App"
.FaceId = 1640
.OnAction = "ExitApp"
.Style = msoButtonIconAndCaption
End With
End With
NewBar.Visible = True
End Sub
Public Sub RemoveCustomToolBar()
Dim cmdBar As CommandBar
For Each cmdBar In Application.CommandBars
If cmdBar.Name = "MyCommandBar" Then
cmdBar.Delete
End If
Next cmdBar
End Sub
Sub RestoreUsersMenuBars()
'Makes the Main Menu Bar Visible
Application.CommandBars("Worksheet Menu Bar").Enabled = True
'Restores users menu bars, gets names from sheet1
Sheet1.Activate
Range("A1").Select
Do While ActiveCell.Value <> vbNullString
Application.CommandBars(ActiveCell.Value).Visible = True
ActiveCell.Offset(1, 0).Select
Loop
End Sub
Public Sub Home()
'Called when you click the Home button
Sheet01.Activate
End Sub
Public Sub ExitApp()
'Called when you click the Exit button
Application.Quit
End Sub