⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 clsframecontrol.cls

📁 AeroSuite--一组非常漂亮的VISTA控件集
💻 CLS
📖 第 1 页 / 共 5 页
字号:
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "clsFrameControl"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit
' Read comments in clsCustomWindow for general information

' APIs used for debugging & can be removed when finalized
Private Declare Function GetMenu Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function GetClientRect Lib "user32" (ByVal hWnd As Long, lpRect As RECT) As Long
Private Declare Function DestroyMenu Lib "user32.dll" (ByVal hMenu As Long) As Long
Private Declare Function IsMenu Lib "user32.dll" (ByVal hMenu As Long) As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Const WM_MOUSEACTIVATE = &H21
Private Const WM_NCRBUTTONDOWN As Long = &HA4
Private Const WM_RBUTTONDOWN As Long = &H204
Private Declare Function SetProp Lib "user32.dll" Alias "SetPropA" (ByVal hWnd As Long, ByVal lpString As String, ByVal hData As Long) As Long

Private Declare Function GetCurrentThreadId Lib "kernel32.dll" () As Long

' API Declarations used in this class
Private Declare Function CreatePen Lib "gdi32.dll" (ByVal nPenStyle As Long, ByVal nWidth As Long, ByVal crColor As Long) As Long
Private Declare Function RemoveProp Lib "user32.dll" Alias "RemovePropA" (ByVal hWnd As Long, ByVal lpString As String) As Long
Private Declare Function GetProp Lib "user32.dll" Alias "GetPropA" (ByVal hWnd As Long, ByVal lpString As String) As Long
Private Declare Function GetMenuItemInfo Lib "user32" Alias "GetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal b As Boolean, lpMenuItemInfo As MENUITEMINFO) As Long
Private Declare Function SetMenuItemInfo Lib "user32.dll" Alias "SetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal bool As Boolean, lpcMenuItemInfo As MENUITEMINFO) As Long
Private Declare Function GetSystemMenu Lib "user32" (ByVal hWnd As Long, ByVal bRevert As Long) As Long
Private Declare Function CreateRectRgn Lib "gdi32.dll" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hWnd As Long, lpRect As RECT) As Long
Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hDC As Long) As Long
Private Declare Function GetDesktopWindow Lib "user32" () As Long
Private Declare Function DrawIconEx Lib "user32" (ByVal hDC As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) As Long
Private Declare Function SetBkMode Lib "gdi32" (ByVal hDC As Long, ByVal nBkMode As Long) As Long
Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Declare Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hDC As Long, ByVal lpStr As String, ByVal nCount As Long, lpRect As RECT, ByVal wFormat As Long) As Long
Private Declare Function SelectObject Lib "gdi32" (ByVal hDC As Long, ByVal hObject As Long) As Long
Private Declare Function FrameRect Lib "user32" (ByVal hDC As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Private Declare Function ReleaseDC Lib "user32" (ByVal hWnd As Long, ByVal hDC As Long) As Long
Private Declare Function FillRect Lib "user32" (ByVal hDC As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Private Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long
Private Declare Function SetTextColor Lib "gdi32" (ByVal hDC As Long, ByVal crColor As Long) As Long
Private Declare Function SelectClipRgn Lib "gdi32" (ByVal hDC As Long, ByVal hRgn As Long) As Long
Private Declare Function CreateRectRgnIndirect Lib "gdi32" (lpRect As RECT) As Long
Private Declare Function GetWindowDC Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function ReleaseCapture Lib "user32" () As Long
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (pDest As Any, pSource As Any, ByVal ByteLen As Long)
Private Declare Function DefWindowProc Lib "user32" Alias "DefWindowProcA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal MSG As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function DeleteDC Lib "gdi32" (ByVal hDC As Long) As Long
Private Declare Function DestroyIcon Lib "user32.dll" (ByVal hIcon As Long) As Long
Private Declare Function RedrawWindow Lib "user32.dll" (ByVal hWnd As Long, lprcUpdate As Any, ByVal hrgnUpdate As Long, ByVal fuRedraw As Long) As Long
Private Declare Function IsIconic Lib "user32.dll" (ByVal hWnd As Long) As Long
Private Declare Function GetForegroundWindow Lib "user32" () As Long
Private Declare Function OffsetRgn Lib "gdi32.dll" (ByVal hRgn As Long, ByVal X As Long, ByVal Y As Long) As Long
Private Declare Function OffsetRect Lib "user32" (lpRect As RECT, ByVal X As Long, ByVal Y As Long) As Long
Private Declare Function SetCapture Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function ClipCursor Lib "user32" (lpRect As Any) As Long
Private Declare Function IsZoomed Lib "user32.dll" (ByVal hWnd As Long) As Long
Private Declare Function PtInRect Lib "user32.dll" (lpRect As RECT, ByVal X As Long, ByVal Y As Long) As Long
Private Declare Function GetRgnBox Lib "gdi32.dll" (ByVal hRgn As Long, lpRect As RECT) As Long
Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
Private Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal Y As Long, ByVal CX As Long, ByVal CY As Long, ByVal wFlags 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, ByVal dwNewLong As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Boolean) As Long
Private Declare Function SetRect Lib "user32.dll" (lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function GetGDIObject Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, lpObject As Any) As Long
Private Declare Function CreateFontIndirect Lib "gdi32" Alias "CreateFontIndirectA" (lpLogFont As LOGFONT) As Long
Private Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, lpvParam As Any, ByVal fuWinIni As Long) As Long
Private Declare Function CopyImage Lib "user32.dll" (ByVal Handle As Long, ByVal un1 As Long, ByVal n1 As Long, ByVal n2 As Long, ByVal un2 As Long) As Long
Private Declare Function GetDoubleClickTime Lib "user32.dll" () As Long
Private Declare Function GetTickCount Lib "kernel32.dll" () As Long
Private Declare Function EqualRect Lib "user32.dll" (lpRect1 As RECT, lpRect2 As RECT) As Long
Private Declare Function DrawMenuBar Lib "user32.dll" (ByVal hWnd As Long) As Long
Private Declare Function ShowWindow Lib "user32.dll" (ByVal hWnd As Long, ByVal nCmdShow As Long) As Long
Private Declare Function GetWindowText Lib "user32.dll" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Private Declare Function PtInRegion Lib "gdi32.dll" (ByVal hRgn As Long, ByVal X As Long, ByVal Y As Long) As Long
Private Declare Function FrameRgn Lib "gdi32.dll" (ByVal hDC As Long, ByVal hRgn As Long, ByVal hBrush As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Private Declare Function FillRgn Lib "gdi32.dll" (ByVal hDC As Long, ByVal hRgn As Long, ByVal hBrush As Long) As Long
Private Declare Function SetForegroundWindow Lib "user32" (ByVal hWnd As Long) As Long
Private Declare Function GetCapture Lib "user32.dll" () As Long
Private Declare Function ExtractIconEx Lib "shell32.dll" Alias "ExtractIconExA" (ByVal lpszFile As String, ByVal nIconIndex As Long, phiconLarge As Long, phiconSmall As Long, ByVal nIcons As Long) As Long
Private Declare Function DrawFrameControl Lib "user32.dll" (ByVal hDC As Long, lpRect As RECT, ByVal un1 As Long, ByVal un2 As Long) As Long
Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Private Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long

' API Constants used in this class
Private Const COLOR_GRADIENTINACTIVECAPTION As Long = 28
Private Const COLOR_GRADIENTACTIVECAPTION As Long = 27
Private Const DFC_BUTTON As Long = 4
Private Const DFC_CAPTION As Long = 1
Private Const DFCS_BUTTONPUSH As Long = &H10
Private Const DFCS_CAPTIONCLOSE As Long = &H0
Private Const DFCS_CAPTIONHELP As Long = &H4
Private Const DFCS_CAPTIONMAX As Long = &H2
Private Const DFCS_CAPTIONMIN As Long = &H1
Private Const DFCS_HOT As Long = &H1000
Private Const DFCS_CAPTIONRESTORE As Long = &H3
Private Const DFCS_INACTIVE As Long = &H100
Private Const DFCS_PUSHED As Long = &H200
Private Const DT_CALCRECT As Long = &H400
Private Const DT_CENTER As Long = &H1
Private Const DT_LEFT As Long = &H0
Private Const DT_SINGLELINE As Long = &H20
Private Const DT_VCENTER As Long = &H4
Private Const IMAGE_ICON As Long = 1
Private Const LR_COPYFROMRESOURCE As Long = &H4000
Private Const GWL_HWNDPARENT = (-8)
Private Const GWL_EXSTYLE As Long = -20
Private Const GWL_STYLE As Long = -16
Private Const GWL_WNDPROC As Long = -4
Private Const HTNOWHERE As Long = 0
Private Const HTCLIENT As Long = 1
Private Const HTCAPTION As Long = 2
Private Const HTSYSMENU As Long = 3
Private Const HTGROWBOX As Long = 4
Private Const HTMENU As Long = 5
Private Const HTMenuPlus As Long = 30 ' custom
Private Const HTMINBUTTON As Long = 8
Private Const HTMAXBUTTON As Long = 9
Private Const HTLEFT As Long = 10
Private Const HTRIGHT As Long = 11
Private Const HTTOP As Long = 12
Private Const HTTOPLEFT As Long = 13
Private Const HTTOPRIGHT As Long = 14
Private Const HTBOTTOM As Long = 15
Private Const HTBOTTOMLEFT As Long = 16
Private Const HTBOTTOMRIGHT As Long = 17
Private Const HTBORDER As Long = 18
Private Const HTCLOSE As Long = 20
Private Const HTHELP As Long = 21
Private Const MIIM_STATE     As Long = &H1&
Private Const MIIM_ID        As Long = &H2&
Private Const MFS_GRAYED As Long = &H3&
Private Const SC_CLOSE = &HF060&
Private Const SC_MOVE As Long = &HF010&
Private Const SC_KEYMENU As Long = &HF100&
Private Const SC_MINIMIZE = &HF020&
Private Const SC_MAXIMIZE As Long = &HF030&
Private Const SC_MOUSEMENU As Long = &HF090
Private Const SC_RESTORE = &HF120&
Private Const SC_SIZE As Long = &HF000&
Private Const SC_MOVE_Clone As Long = &H7AA ' custom
Private Const SC_SIZE_Clone As Long = &H7AB ' custom
Private Const SC_CLOSE_Clone = &H7AC ' custom
Private Const SC_MINIMIZE_Clone = &H7AD ' custom
Private Const SC_RESTORE_Clone = &H7AE ' custom
Private Const SC_MAXIMIZE_Clone As Long = &H7AF ' custom
Private Const SM_CYICON As Long = 12
Private Const SM_CXICON As Long = 11
Private Const SM_CXDLGFRAME As Long = 7
Private Const SM_CYDLGFRAME As Long = 8
Private Const SM_CXBORDER As Long = 5
Private Const SM_CYBORDER As Long = 6
Private Const SM_CYSMCAPTION As Long = 51
Private Const SM_CYCAPTION As Long = 4
Private Const SM_CXFRAME As Long = 32
Private Const SM_CYFRAME As Long = 33
Private Const SM_CXSIZE As Long = 30
Private Const SM_CYSIZE As Long = 31
Private Const SM_CXSMICON As Long = 49
Private Const SM_CYSMICON As Long = 50
Private Const SM_CXMINTRACK As Long = 34
Private Const SM_CYMINTRACK As Long = 35
Private Const SPI_GETWORKAREA As Long = 48
Private Const WM_APPACTIVATE As Long = &H1C
Private Const WM_CANCELMODE As Long = &H1F
Private Const WM_CLOSE As Long = &H10
Private Const WM_COMMAND As Long = &H111
Private Const WM_CONTEXTMENU As Long = &H7B
Private Const WM_DESTROY As Long = &H2
Private Const WM_GETICON As Long = &H7F
Private Const WM_GETMINMAXINFO As Long = &H24
Private Const WM_GETSYSMENU = &H313
Private Const WM_GETTEXT As Long = &HD
Private Const WM_LBUTTONUP As Long = &H202
Private Const WM_LBUTTONDOWN As Long = &H201
Private Const WM_MBUTTONDOWN As Long = &H207
Private Const WM_MOUSEMOVE As Long = &H200
Private Const WM_NCACTIVATE As Long = &H86
Private Const WM_NCCALCSIZE As Long = &H83
Private Const WM_NCHITTEST As Long = &H84
Private Const WM_NCLBUTTONDBLCLK As Long = &HA3
Private Const WM_NCLBUTTONDOWN As Long = &HA1
Private Const WM_NCLBUTTONUP As Long = &HA2
Private Const WM_NCMOUSEMOVE As Long = &HA0
Private Const WM_NCPAINT As Long = &H85
Private Const WM_NCRBUTTONUP As Long = &HA5
Private Const WM_SETCURSOR As Long = &H20
Private Const WM_SETREDRAW As Long = &HB
Private Const WM_SETICON As Long = &H80
Private Const WM_SETTEXT As Long = &HC
Private Const WM_SIZE = &H5
Private Const WM_STYLECHANGED = &H7D
Private Const WM_SYSCOMMAND As Long = &H112
Private Const WM_WINDOWPOSCHANGED As Long = &H47
Private Const WM_XBUTTONDOWN As Long = &H20B
Private Const WS_BORDER As Long = &H800000
Private Const WS_CAPTION As Long = &HC00000
Private Const WS_CLIPCHILDREN As Long = &H2000000
Private Const WS_CLIPSIBLINGS As Long = &H4000000
Private Const WS_DLGFRAME As Long = &H400000
Private Const WS_EX_APPWINDOW As Long = &H40000
Private Const WS_EX_TOOLWINDOW As Long = &H80&
Private Const WS_MAXIMIZE As Long = &H1000000
Private Const WS_MAXIMIZEBOX As Long = &H10000
Private Const WS_MINIMIZE As Long = &H20000000
Private Const WS_MINIMIZEBOX As Long = &H20000
Private Const WS_SYSMENU As Long = &H80000
Private Const WS_THICKFRAME As Long = &H40000
Private Const WS_VISIBLE As Long = &H10000000
Private Const WVR_VALIDRECTS As Long = &H400


' API UDTs and Custom UDTs
Private Type LOGFONT        ' used to create fonts
    lfHeight As Long
    lfWidth As Long
    lfEscapement As Long
    lfOrientation As Long
    lfWeight As Long
    lfItalic As Byte
    lfUnderline As Byte
    lfStrikeOut As Byte
    lfCharSet As Byte
    lfOutPrecision As Byte
    lfClipPrecision As Byte
    lfQuality As Byte
    lfPitchAndFamily As Byte
    lfFaceName As String * 32
End Type
Private Type NONCLIENTMETRICS     ' used to retrieve/set system settings
    cbSize As Long
    iBorderWidth As Long
    iScrollWidth As Long
    iScrollHeight As Long
    iCaptionWidth As Long
    iCaptionHeight As Long
    lfCaptionFont As LOGFONT
    iSMCaptionWidth As Long
    iSMCaptionHeight As Long
    lfSMCaptionFont As LOGFONT
    iMenuWidth As Long
    iMenuHeight As Long
    lfMenuFont As LOGFONT
    lfStatusFont As LOGFONT
    lfMessageFont As LOGFONT
End Type
Private Type StyleStructure  ' used when window style changing or changed
    StyleOld As Long
    StyleNew As Long
End Type
Private Type NCCALCSIZE_PARAMS  ' used when client rect needs to be calculated
   rgrc(0 To 2) As RECT
   lppos As Long 'pointer to WINDOWPOS
End Type
Private Type MINMAXINFO         ' used when sizing a window
    ptReserved As POINTAPI
    ptMaxSize As POINTAPI
    ptMaxPosition As POINTAPI
    ptMinTrackSize As POINTAPI
    ptMaxTrackSize As POINTAPI
End Type
Private Type WINDOWPOS          ' used when sizing or moving
   hWnd As Long
   hWndInsertAfter As Long
   X As Long
   Y As Long
   CX As Long
   CY As Long
   Flags As Long

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -