User32.dll
CallWindowProcA |
CallNextHookEx |
CloseClipboard |
EmptyClipboard |
EnableWindow |
EnumDisplayDevices |
EnumDisplayMonitors |
EnumDisplaySettings |
FindWindow |
FindWindowEx |
GetAsyncKeyState |
GetClassName |
GetClipboardData |
GetClipboardSequenceNumber |
GetDC |
GetForegroundWindow |
GetParent |
GetSysColor |
GetSystemMetrics |
GetWindow |
GetWindowLongPtr |
GetWindowRect |
GetWindowText |
GetWindowThreadProcessId |
IsClipboardFormatAvailable |
LockWindowUpdate |
MonitorFromWindow |
OpenClipboard |
PostMessage |
PutFocus |
ReleaseDC |
ScrollWindowEx |
SetClipboardData |
SetDlgItemText |
SetForegroundWindow |
SetWindowPos |
ShowWindow |
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
CallNextHookEx
Private Declare PtrSafe Function CallNextHookEx Lib "USER32" _
(ByVal hHook As LongPtr, ByVal nCode As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr
CloseClipboard
Private Declare PtrSafe Function CloseClipboard Lib "USER32" () As LongPtr
EmptyClipboard
Private Declare PtrSafe Function EmptyClipboard Lib "USER32" () As Long
EnumDisplayDevices
Private Declare PtrSafe Function EnumDisplayDevices Lib "USER32" Alias "EnumDisplayDevicesW" (ByVal lpDevice As LongPtr, ByVal iDevNum As Long, ByRef lpDisplayDevice As DISPLAY_DEVICEW, ByVal dwFlags As Long) As Long
EnumDisplayMonitors
Private Declare PtrSafe Function EnumDisplayMonitors Lib "USER32" (ByVal hdc As Long, lprcClip As Any, ByVal lpfnEnum As LongPtr, dwData As Long) As Long
EnumDisplaySettings
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-enumdisplaysettingsa
Private Declare PtrSafe Function EnumDisplaySettings Lib "USER32" Alias "EnumDisplaySettingsA" _
(ByVal lpszDeviceName As String, _
ByVal iModeNum As Long, _
lpDevMode As DEVMODE) As LongPtr
FindWindow
Private Declare PtrSafe Function FindWindow Lib "USER32" Alias "FindWindowA" _
(ByVal lpClassName As String, _
ByVal lpWindowName As String) As LongPtr
FindWindowEx
Private Declare PtrSafe Function FindWindowEx Lib "user32.dll" Alias "FindWindowExA" ( _
ByVal hWnd1 As Long, _
ByVal hWnd2 As Long, _
ByVal lpsz1 As String, _
ByVal lpsz2 As String _
) As Long
GetAsyncKeyState
link - http://www.cpearson.com/excel/keytest.aspx
Detect Key Stroke
Private Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
Private Const VK_F9 = &H78
Sub WaitUntilF9Key()
Do Until GetAsyncKeyState(VK_F9)
DoEvents
Loop
MsgBox "Hello World"
End Sub
GetClipboardSequenceNumber
Private Declare PtrSafe Function GetClipboardSequenceNumber Lib "USER32" () As Long
GetMonitorInfo
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-getmonitorinfoa
Private Declare PtrSafe Function GetMonitorInfo Lib "USER32" Alias "GetMonitorInfoA" _
(ByVal hMonitor As LongPtr, _
ByRef lpMI As MONITORINFOEX) As Boolean
Private Const MONITOR_CCHDEVICENAME As Long = 32 'MONITORINFOEX.szDevice: device name fixed length
Private Type MONITORINFOEX
cbSize As Long
rcMonitor As RECT
rcWork As RECT
dwFlags As Long
szDevice As String * MONITOR_CCHDEVICENAME
End Type
GetSysColor
Private Declare PtrSafe Function GetSysColor Lib "USER32" (ByVal nIndex As Long) As Long
GetSystemMetrics
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-getsystemmetrics
Private Declare PtrSafe Function GetSystemMetrics Lib "USER32" _
(ByVal nIndex As Long) As Long
GetWindowLong
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-getwindowlonga
Private Declare PtrSafe Function GetWindowLong Lib "USER32" _
Alias "GetWindowLongA" ( _
ByVal Hwnd As LongPtr, _
ByVal nIndex As Long) As Long
#If Win64 Then
Declare PtrSafe Function GetWindowLongPtr Lib "USER32" Alias "GetWindowLongPtrA" (ByVal Hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
'https://docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-getwindowlongptra
Declare PtrSafe Function SetWindowLongPtr Lib "USER32" Alias "SetWindowLongPtrA" (ByVal Hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
'https://docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-setwindowlongptra
#Else
Declare PtrSafe Function GetWindowLongPtr Lib "USER32" Alias "GetWindowLongA" (ByVal Hwnd As LongPtr, ByVal nIndex As Long) As LongPtr
Declare PtrSafe Function SetWindowLongPtr Lib "USER32" Alias "SetWindowLongA" (ByVal Hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
#End If
GetWindowRect
Private Declare PtrSafe Function GetWindowRect Lib "USER32" _
(ByVal Hwnd As LongPtr, _
lpRect As RECT) As Long
LockWindowUpdate
Private Declare PtrSafe Function LockWindowUpdate Lib "USER32" _
(ByVal hwndLock As Long) As Long
MonitorFromWindow
Public Declare PtrSafe Function MonitorFromWindow Lib "USER32" _
(ByVal Hwnd As LongPtr, _
ByVal dwFlags As Long) As LongPtr
Public Const MONITOR_DEFAULTTONULL As Long = 0 'dwFlags: Returns NULL
OpenClipboard
Private Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hwnd As LongPtr) As Long
Putfocus
Private Declare PtrSafe Function Putfocus Lib "USER32" Alias "SetFocus" ( _
ByVal Hwnd As LongPtr) As LongPtr
ScrollWindowEx
Private Declare PtrSafe Function ScrollWindowEx Lib "USER32" _
(ByVal Hwnd As LongPtr, _
ByVal dx As Long, _
ByVal dy As Long, _
lprcScroll As Any, _
lprcClip As Any, _
ByVal hrgnUpdate As LongPtr, _
lprcUpdate As Any, _
ByVal fuScroll As Long) As Long
Const SW_SCROLLCHILDREN = &H1
Const SW_INVALIDATE = &H2
Const SW_ERASE = &H4
SetClipboardData
Private Declare PtrSafe Function SetClipboardData Lib "USER32" (ByVal wFormat As LongPtr, ByVal hMem As LongPtr) As LongPtr
SetDlgItemText
Private Declare PtrSafe Function SetDlgItemText Lib "USER32" Alias "SetDlgItemTextA" _
(ByVal hDlg As LongPtr, ByVal nIDDlgItem As Long, ByVal lpString As String) As Long
SetForegroundWindow
Public Declare PtrSafe Function SetForegroundWindow Lib "USER32" ( _
ByVal Hwnd As LongPtr) As Long
SetWindowLong
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-setwindowlonga
Private Declare PtrSafe Function SetWindowLong Lib "USER32" _
Alias "SetWindowLongA" ( _
ByVal Hwnd As LongPtr, _
ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
SetWindowPos
Private Declare PtrSafe Function SetWindowPos Lib "USER32" _
(ByVal Hwnd As LongPtr, _
ByVal hWndInsertAfter As LongPtr, _
ByVal x As Long, _
ByVal y As Long, _
ByVal cx As Long, _
ByVal cy As Long, _
ByVal wFlags As Long) As Long
SetWindowsHookEx
Private Declare PtrSafe Function SetWindowsHookEx Lib "USER32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As LongPtr, ByVal hmod As LongPtr, ByVal dwThreadId As Long) As LongPtr
ShowWindow
link - docs.microsoft.com/en-us/windows/win32/api/winuser/nf-winuser-showwindow
Private Declare PtrSafe Function ShowWindow Lib "USER32" _
(ByVal Hwnd As LongPtr, _
ByVal nCmdSHow As Long) As Long
UnhookWindowsHookEx
Private Declare PtrSafe Function UnhookWindowsHookEx Lib "USER32" _
(ByVal hHook As LongPtr) As Long
© 2025 Better Solutions Limited. All Rights Reserved. © 2025 Better Solutions Limited TopPrevNext