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

📄 msgdocking.bas

📁 vb做的数据库 客户管理系统
💻 BAS
📖 第 1 页 / 共 2 页
字号:
Attribute VB_Name = "msgDocking"
Option Explicit

'Some API Declarations
Private Type POINTAPI
    X As Long
    Y As Long
End Type

Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type

Private Declare Function MoveWindow Lib "user32" (ByVal hwnd As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint 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 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 Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (pDest As Any, pSrc As Any, ByVal ByteLen As Long)

Private Declare Function SystemParametersInfo_Rect Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, lpvParam As RECT, ByVal fuWinIni As Long) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) 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 Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) 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 OffsetRect Lib "user32" (lpRect As RECT, ByVal X As Long, ByVal Y As Long) As Long

Private Const SWP_NOSIZE = &H1
Private Const SWP_NOZORDER = &H4
Private Const SWP_NOACTIVATE = &H10

Private Const WM_MOVING = &H216
Private Const WM_SIZING = &H214
Private Const WM_ENTERSIZEMOVE = &H231
Private Const WM_EXITSIZEMOVE = &H232

Private Const GWL_WNDPROC = (-4)
Private Const GWL_STYLE = (-16)

Private Const SPI_GETWORKAREA = 48

Private Const WMSZ_LEFT = 1
Private Const WMSZ_TOPLEFT = 4
Private Const WMSZ_BOTTOMLEFT = 7
Private Const WMSZ_TOP = 3
Private Const WMSZ_TOPRIGHT = 5

'User Declarations
'-----------------
Private Enum SnapFormMode
    Moving = 1
    Sizing = 2
End Enum

'We save the Infos in an UDT. That's easier to organize
Private Type DockingLog
    hwnd As Long
    oldProc As Long
End Type

Private m_hMasterWnd As Long

Private Logs() As DockingLog, LogCount As Integer, MaxLogs As Integer

Private MouseX As Long, MouseY As Long
Public SnappedX As Boolean, SnappedY As Boolean
Public Rects() As RECT

Private Const SnapWidth = 10

Private Const DoSubClass As Boolean = True

'Deactivate Docking
Public Sub DockingTerminate(f As Form)
    Dim t As Integer, H As Long
    
    H = f.hwnd
    
    'delete entry as master form
    If m_hMasterWnd = H Then m_hMasterWnd = 0
    
    'Search Window
    For t = 0 To LogCount - 1
        If Logs(t).hwnd = H Then
            'Set back to Default WindowProc
            SetWindowLong H, GWL_WNDPROC, Logs(t).oldProc
            'Delete Window-Entry in Array
            For H = t To LogCount - 2
                Logs(H) = Logs(H + 1)
            Next H
            LogCount = LogCount - 1
            Exit For
        End If
    Next t
        
End Sub

'Activate Docking
Public Sub DockingStart(ByVal f As Form, Optional ByVal IsMaster As Boolean = False)
    Dim H As Long, t As Integer
    
    If Not DoSubClass Then Exit Sub
    
    'We redim only in 10 steps. This won't slow the Programm!
    If LogCount + 10 > MaxLogs Then
        MaxLogs = LogCount + 10
        ReDim Preserve Logs(MaxLogs)
    End If
    
    For t = 0 To LogCount - 1
        If Logs(t).hwnd = f.hwnd Then
            Debug.Print "Window-Docking already activated!"
            Exit Sub
        End If
    Next t

    H = f.hwnd
    Logs(LogCount).hwnd = H
    
    'Starting Subclassing and saving the old Window Procedure.
    Logs(LogCount).oldProc = SetWindowLong(H, GWL_WNDPROC, AddressOf WindowProc)

    'Set master status, if requested
    If IsMaster Then m_hMasterWnd = f.hwnd

    LogCount = LogCount + 1
    
End Sub

Public Function WindowProc(ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    Dim t As Integer ' Counter-Variable
    Dim oldProc As Long ' Address of original WindowProc
    Dim r As RECT, p As POINTAPI
    Dim runProc As Boolean
    Dim frm As Form
    runProc = True
    
    Dim rStartPos As RECT
    
    'Search Window in Array
    For t = 0 To LogCount - 1
        If Logs(t).hwnd = hwnd Then
            oldProc = Logs(t).oldProc
            Exit For
        End If
    Next t
    
    If oldProc = 0 Then Exit Function 'This would be not very good... ;-)
    
    If wMsg = WM_ENTERSIZEMOVE Then 'Windows tells us, that the User
                                    'begins to move or resize the Window.
        GetWindowRect hwnd, r
        GetCursorPos p
        MouseX = p.X - r.Left
        MouseY = p.Y - r.Top
        
        GetFrmRects hwnd
        
    ElseIf wMsg = WM_SIZING Or wMsg = WM_MOVING Then 'While moving/sizing we're changing the Window Position/Size
                    
        'Get the rect info for the master window's current position (stored in twips)
        GetWindowRect hwnd, rStartPos
                    
        'Get the Rect-Structure from the Pointer located in lParam
        CopyMemory r, ByVal lParam, Len(r)
        
        'Change the Rect(see in DockFormRect)
        If wMsg = WM_SIZING Then
          DockFormRect hwnd, Sizing, r, wParam
        Else
          DockFormRect hwnd, Moving, r, wParam, MouseX, MouseY
        End If
        
        'Save it back.
        CopyMemory ByVal lParam, r, Len(r)
        
        'was this the master form we just moved?
        If hwnd = m_hMasterWnd Then
          
          Dim rTemp As RECT
          
          'examine all known docking-windows for their positions
          For t = 0 To LogCount - 1

            'but don't look at myself
            If Logs(t).hwnd <> hwnd Then
            
              'Get the window location of the candidate window
              GetWindowRect Logs(t).hwnd, rTemp
              
              'was this window docked to me in any way before i moved just now?
              If (rStartPos.Top = rTemp.Bottom) Or _
                 (rStartPos.Bottom = rTemp.Top) Or _
                 (rStartPos.Left = rTemp.Right) Or _
                 (rStartPos.Right = rTemp.Left) Then
                  
                'Calculate the delta for this window
                Dim nNewLeft As Long, nNewTop As Long
                nNewLeft = rTemp.Left + (r.Left - rStartPos.Left)
                nNewTop = rTemp.Top + (r.Top - rStartPos.Top)
                
                'Don't change the window's height and width...
                Dim nWidth As Long, nHeight As Long
                nWidth = rTemp.Right - rTemp.Left
                nHeight = rTemp.Bottom - rTemp.Top
                
                'update this Window's Position
                Call MoveWindow(Logs(t).hwnd, nNewLeft, nNewTop, nWidth, nHeight, 1)
                
              End If
            End If
          Next
          
        End If
        
        'Return a true Value(API uses 1 as True-Value)
        WindowProc = 1
        
        runProc = False 'Don't run OldWindowProc
    End If
    
    'Nachricht an originale Routine weiterleiten
    If runProc Then WindowProc = CallWindowProc(oldProc, hwnd, wMsg, wParam, lParam)
    
End Function

Private Function GetFrmRects(ByVal hwnd As Long)
  Dim frm     As Form
  Dim i       As Integer
  
  ReDim Rects(0 To 0)
  SystemParametersInfo_Rect SPI_GETWORKAREA, vbNull, Rects(0), 0
  
  i = 1
  
  For Each frm In Forms
    If frm.Visible And Not frm.hwnd = hwnd Then
      ReDim Preserve Rects(0 To i)
      GetWindowRect frm.hwnd, Rects(i)
      
      i = i + 1
    End If
  Next frm
End Function

⌨️ 快捷键说明

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