QueryClose Event

It is not possible to remove the "x" from the top right corner although you can disable it.
Whether you display a prompt to the user or not is up to you.
Using the QueryClose event allows you to intercept the message to close the userform before it is actually closed.
If you set the Cancel paramater to True, then the userform will not be closed.
This means the userform has been closed by the user pressing the top right x.

Private Sub UserForm_QueryClose(Cancel as integer, CloseMode as integer) 
   If CloseMode = vbQueryClose.vbFormControlMenu Then
      cmdCancel.SetFocus
      MsgBox "Cannot close the userform !!"
      Cancel = True
   End If
End Sub

This means the userform has been closed by code

If CloseMode = vbQueryClose.vbFormCode Then 
   Cancel = True
End If

Removing the Close button

'userform window
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" _
   (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

'current window state
Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" _
   (ByVal hwnd As Long, ByVal nIndex As Long) As Long

'new window style
Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" _
   (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long

Const GWL_STYLE = -16
Const WS_SYSMENU = &H80000

Public Sub RemoveCloseButton(oUserForm As MSForms.UserForm)
Dim hwnd As Long
Dim lStyle As Long

   hwnd = FindWindow("ThunderXFrame"), oUserForm.Caption)

   lStyle = GetWindowLong(hwnd, GWL_STYE)
   SetWindowLong hwnd, GWL_STYLE, (lStyle And Not WS_SYSMENU)
End Sub

© 2024 Better Solutions Limited. All Rights Reserved. © 2024 Better Solutions Limited TopPrevNext