Vba Code to disable Unhide option in menubar

jagdish_patel

New Member
Joined
Jan 11, 2020
Messages
14
Office Version
  1. 2007
Platform
  1. Windows
Hi,
I am very new to get help from mrexcel.com
I want to disable Unhide option of Menubar. i got the following code for that but it is not working for me

Dim WBname As Window
Set WBname = Windows("Accounting.xlsm") 'You can use Windows("[Workbook Name]") as well
Application.CommandBars("Insert").Controls(4).Enabled = False
Application.CommandBars("Worksheet Menu Bar").Controls("Format").Controls("Sheet").Controls("Unhide...").Enabled = False

even after above code unhide option is not disabled. anybody can see that window.
where i am wrong. or what is correct code.

I would be very much grateful, please anybody can help me.
 

Excel Facts

Move date out one month or year
Use =EDATE(A2,1) for one month later. Use EDATE(A2,12) for one year later.
Please explain what you are trying to achieve overall? If you don't want people to Unhide sheets, then hide them as xlVeryHidden, and they will not be visible from the Unhide menu. Just guessing.
 
Upvote 0
Please explain what you are trying to achieve overall? If you don't want people to Unhide sheets, then hide them as xlVeryHidden, and they will not be visible from the Unhide menu. Just guessing.

Thanks for your reply, but I know that xlVeryHidden can hide sheet, which no one can see

it is not sheet, it is workbook in hidden window, which one can see by unhiding
so i want to disable unhide option in menu bar.
really very thankful for your reply
 
Upvote 0
I have macro file in workbook, which I kept in hidden window. but by unhide option on menubar it can be seen and can be unhide.
I dont want any body can see that file.
 
Upvote 0
Can I ask why you haven't saved it as an Add-In?
 
Upvote 0
it is not sheet, it is workbook in hidden window, which one can see by unhiding
so i want to disable unhide option in menu bar.
really very thankful for your reply

I dont have excel 2007 anymore (which i can see that you are using from your forum signature) so I can't test if protecting the workbook Structure and Windows works : Review Tab>Protect Workbook ...

As for disabling the Unhide menu from the View tab in the Ribbon, the standard way is by using XML ... Take a look here: Change the Ribbon in Excel 2007 and up

A third unorthodox alternative should IMO be possible using the windows API ( Note: The following code will only work in MDI excel -ie: excel 2010 and earlier versions)


In a Standard Module:
VBA Code:
Option Explicit

#If VBA7 Then
    Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow As Long) As Long
    Private Declare PtrSafe Function UpdateWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
#Else
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
#End If


Public Property Let WorkBookVisible(ByVal Wbook As Workbook, ByVal Visible As Boolean)

    #If VBA7 Then
        Dim hwnd As LongPtr
    #Else
        Dim hwnd As Long
    #End If
   
    hwnd = GetWorkbook_Hwnd_From_Name(Wbook.Name)
    Application.EnableEvents = False
    ShowWindow hwnd, -CLng(Visible)
    UpdateWindow hwnd
    Application.EnableEvents = True
   
End Property


#If VBA7 Then
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As LongPtr
    Dim hDsk As LongPtr, hWb As LongPtr
#Else
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As Long
    Dim hDsk As Long, hWb As Long
#End If

    Dim sBuffer As String * 256, lRet As Long

    hDsk = FindWindowEx(Application.hwnd, 0, "XLDESK", vbNullString)
    Do
        hWb = FindWindowEx(hDsk, hWb, "EXCEL7", vbNullString)
        lRet = GetWindowText(hWb, sBuffer, 256)
        If InStr(1, Left(sBuffer, lRet), Left(WbookName, InStrRev(WbookName, ".") - 1), vbTextCompare) Then
            GetWorkbook_Hwnd_From_Name = hWb
            Exit Function
        End If
        DoEvents
    Loop Until hWb = 0

End Function



Code Usage :
VBA Code:
'Change Workbook name as required.

Sub ShowWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = True
End Sub

Sub HideWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = False
End Sub
 
Upvote 0
This is a more accurate code so please ignore the previous one and use this:


In a Standard Module:
VBA Code:
Option Explicit

#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
    #Else
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As Long) As LongPtr
    #End If
    Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow As Long) As Long
    Private Declare PtrSafe Function UpdateWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As LongPtr, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As LongPtr
#Else
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As Long, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
    Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
    Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
#End If



Public Property Let WorkBookVisible(ByVal Wbook As Workbook, ByVal Visible As Boolean)

    #If VBA7 Then
        Dim hwnd As LongPtr
    #Else
        Dim hwnd As Long
    #End If
    
    Const GWL_EXSTYLE = (-20)
    Const WS_EX_LAYERED = &H80000
    Const LWA_ALPHA = &H2&

    hwnd = GetWorkbook_Hwnd_From_Name(Wbook.Name)
    Application.EnableEvents = False
    ShowWindow hwnd, -CLng(Visible)
    Call SetWindowLong(hwnd, GWL_EXSTYLE, GetWindowLong(hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED)
    Call SetLayeredWindowAttributes(hwnd, 0, IIf(Visible = False, 0, 255), LWA_ALPHA)
    UpdateWindow hwnd
    Application.EnableEvents = True

End Property


#If VBA7 Then
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As LongPtr
    Dim hDsk As LongPtr, hWb As LongPtr
#Else
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As Long
    Dim hDsk As Long, hWb As Long
#End If

    Dim sBuffer As String * 256, lRet As Long

    hDsk = FindWindowEx(Application.hwnd, 0, "XLDESK", vbNullString)
    Do
        hWb = FindWindowEx(hDsk, hWb, "EXCEL7", vbNullString)
        lRet = GetWindowText(hWb, sBuffer, 256)
        If InStr(1, Left(sBuffer, lRet), Left(WbookName, InStrRev(WbookName, ".") - 1), vbTextCompare) Then
            GetWorkbook_Hwnd_From_Name = hWb
            Exit Function
        End If
        DoEvents
    Loop Until hWb = 0

End Function



Code Usage :
VBA Code:
'Change Workbook name as required.

Sub ShowWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = True
End Sub

Sub HideWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = False
End Sub
 
Upvote 0
Can I ask why you haven't saved it as an Add-In?

Hi GlennUK

I overlooked your answer ... but now that I think about it,, I guess it is the best answer without needing tons of code.

Without having to save the workbook as an add-in , we can just set the IsAddin Property to TRUE either in the VBE Properties window or via code:
VBA Code:
 ThisWorkbook.IsAddin = True
ThisWorkbook.Save

Not sure if there will be any undesirable side-effects though.

Thanks.
 
Upvote 0
This is a more accurate code so please ignore the previous one and use this:


In a Standard Module:
VBA Code:
Option Explicit

#If VBA7 Then
    #If Win64 Then
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
    #Else
        Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
        Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As Long) As LongPtr
    #End If
    Private Declare PtrSafe Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr
    Private Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare PtrSafe Function ShowWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal nCmdShow As Long) As Long
    Private Declare PtrSafe Function UpdateWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As LongPtr, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As LongPtr
#Else
    Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
    Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
    Private Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long
    Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As Long, ByVal crey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
    Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
    Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
#End If



Public Property Let WorkBookVisible(ByVal Wbook As Workbook, ByVal Visible As Boolean)

    #If VBA7 Then
        Dim hwnd As LongPtr
    #Else
        Dim hwnd As Long
    #End If
   
    Const GWL_EXSTYLE = (-20)
    Const WS_EX_LAYERED = &H80000
    Const LWA_ALPHA = &H2&

    hwnd = GetWorkbook_Hwnd_From_Name(Wbook.Name)
    Application.EnableEvents = False
    ShowWindow hwnd, -CLng(Visible)
    Call SetWindowLong(hwnd, GWL_EXSTYLE, GetWindowLong(hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED)
    Call SetLayeredWindowAttributes(hwnd, 0, IIf(Visible = False, 0, 255), LWA_ALPHA)
    UpdateWindow hwnd
    Application.EnableEvents = True

End Property


#If VBA7 Then
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As LongPtr
    Dim hDsk As LongPtr, hWb As LongPtr
#Else
    Function GetWorkbook_Hwnd_From_Name(ByVal WbookName As String) As Long
    Dim hDsk As Long, hWb As Long
#End If

    Dim sBuffer As String * 256, lRet As Long

    hDsk = FindWindowEx(Application.hwnd, 0, "XLDESK", vbNullString)
    Do
        hWb = FindWindowEx(hDsk, hWb, "EXCEL7", vbNullString)
        lRet = GetWindowText(hWb, sBuffer, 256)
        If InStr(1, Left(sBuffer, lRet), Left(WbookName, InStrRev(WbookName, ".") - 1), vbTextCompare) Then
            GetWorkbook_Hwnd_From_Name = hWb
            Exit Function
        End If
        DoEvents
    Loop Until hWb = 0

End Function



Code Usage :
VBA Code:
'Change Workbook name as required.

Sub ShowWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = True
End Sub

Sub HideWorkbook()
    WorkBookVisible(Wbook:=Workbooks("Accounting.xlsm")) = False
End Sub
My workbook is not visible, but problem is any one can see them by unhideoption of menubar
 
Upvote 0

Forum statistics

Threads
1,215,064
Messages
6,122,937
Members
449,094
Latest member
teemeren

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top