자주쓰는 API 중 64비트 호환을 위한 API선언 모음입니다.

 

#If VBA7 Then
    Public Declare PtrSafe Function SetTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, _
        ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr
    Public Declare PtrSafe Function KillTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long
    
    Public Declare PtrSafe Function sndPlaySound32 Lib "winmm.dll" Alias "sndPlaySoundA" ( _
        ByVal lpszSoundName As String, ByVal uFlags As Long) As Long
      
    Public Declare PtrSafe Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" _
    	(ByVal lpstrCommand As String, ByVal lpstrReturnString As Any, _
    	ByVal uReturnLength As Long, ByVal hwndCallback As LongPtr) As Long
    
    Public Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
    
    Public Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As LongPtr)
    
    Public TimerID As LongPtr
    
#Else
    Public Declare Function SetTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long, _
        ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
    Public Declare Function KillTimer Lib "user32" (ByVal hwnd As Long, ByVal nIDEvent As Long) As Long
    
    Public Declare Function sndPlaySound32 Lib "winmm.dll" Alias "sndPlaySoundA" _
       (ByVal lpszSoundName As String, ByVal uFlags As Long) As Long
    
    Public Declare Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" _
    	(ByVal lpstrCommand As String, ByVal lpstrReturnString As Any, _
    	ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long 
        
    Public Declare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) 
    
    Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
           
    Public TimerID As Long
    
#End If

 

https://docs.microsoft.com/en-us/office/vba/language/concepts/getting-started/64-bit-visual-basic-for-applications-overview

 

64-bit Visual Basic for Applications overview

64-bit Visual Basic for Applications overview In this article --> Microsoft Visual Basic for Applications (VBA) is the version of Visual Basic that ships with Microsoft Office. In Microsoft Office 2010, VBA includes language features that enable VBA code t

docs.microsoft.com

 

Office 2010 Help Files: Win32API_PtrSafe with 64-bit Support

 

https://www.microsoft.com/en-us/download/details.aspx?id=9970

 

Office 2010 Help Files: Win32API_PtrSafe with 64-bit Support

Windows API Declarations and Constants for Visual Basic (Updated for the 64-bit version of Microsoft Office 2010) provides declarations for Microsoft Visual Basic programmers who want to call Windows API routines. This file is updated to include calls to t

www.microsoft.com

ptrsafe64bit.EXE
0.52MB
Win32API_PtrSafe.TXT
0.66MB

 

덜 자주쓰는 API

더보기
#If Win64 Then
    Public Declare PtrSafe Function GetForegroundWindow Lib "user32.dll" () As LongPtr
    Public Declare PtrSafe Function SetFocus Lib "user32" (ByVal Hwnd As LongPtr) As Long
    Public Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As LongPtr) As Long
    Public Declare PtrSafe Function EnumChildWindows Lib "user32" (ByVal hWndParent As LongPtr, ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Long
    Public Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal Hwnd As LongPtr, lpRect As RECT) As Long
    Public Declare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
    Public Declare PtrSafe Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As LongPtr)
    Public Declare PtrSafe Function MapVirtualKey Lib "user32" Alias "MapVirtualKeyA" (ByVal wCode As Long, ByVal wMapType As Long) As Long

    Private ShapeHwnd As LongPtr
#Else
    Public Declare Function GetForegroundWindow Lib "user32" () As Long
    Public Declare Function SetFocus Lib "user32" (ByVal Hwnd As Long) As Long
    Public Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal Hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
    Public Declare Function EnumChildWindows Lib "user32" (ByVal hWndParent As Long, ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
    Public Declare Function GetWindowRect Lib "user32" (ByVal Hwnd As Long, lpRect As RECT) As Long
    Public Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
    Public Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
    Public Declare Function MapVirtualKey Lib "user32" Alias "MapVirtualKeyA" (ByVal wCode As Long, ByVal wMapType As Long) As Long
    
    Private ShapeHwnd As Long
#End If

 

 클립보드 관련 API이용법:

더보기
Option Explicit


#If VBA7 Then

   Private Declare PtrSafe Function OpenClipboard Lib "User32" (ByVal hWnd As LongPtr) As LongPtr
   Private Declare PtrSafe Function EmptyClipboard Lib "User32" () As LongPtr
   Private Declare PtrSafe Function CloseClipboard Lib "User32" () As LongPtr
   Private Declare PtrSafe Function IsClipboardFormatAvailable Lib "User32" (ByVal wFormat As LongPtr) As LongPtr
   Private Declare PtrSafe Function GetClipboardData Lib "User32" (ByVal wFormat As LongPtr) As LongPtr
   Private Declare PtrSafe Function SetClipboardData Lib "User32" (ByVal wFormat As LongPtr, ByVal hMem As LongPtr) As LongPtr
   Private Declare PtrSafe Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As LongPtr
   Private Declare PtrSafe Function GlobalLock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
   Private Declare PtrSafe Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
   Private Declare PtrSafe Function GlobalSize Lib "kernel32" (ByVal hMem As LongPtr) As Long
   Private Declare PtrSafe Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Any, ByVal lpString2 As Any) As LongPtr
   Private Declare PtrSafe Function PasteToObj Lib "User32" Alias "SendMessageA" (ByVal hWnd As Long, Optional ByVal wMsg As Long = &H302, Optional ByVal wParam As Long = 0, Optional lParam As Any = 0&) As Long

#Else
   
   Private Declare Function OpenClipboard Lib "user32.dll" (ByVal hWnd As Long) As Long
   Private Declare Function EmptyClipboard Lib "user32.dll" () As Long
   Private Declare Function CloseClipboard Lib "user32.dll" () As Long
   Private Declare Function IsClipboardFormatAvailable Lib "user32.dll" (ByVal wFormat As Long) As Long
   Private Declare Function GetClipboardData Lib "user32.dll" (ByVal wFormat As Long) As Long
   Private Declare Function SetClipboardData Lib "user32.dll" (ByVal wFormat As Long, ByVal hMem As Long) As Long
   Private Declare Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
   Private Declare Function GlobalLock Lib "kernel32.dll" (ByVal hMem As Long) As Long
   Private Declare Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As Long) As Long
   Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
   Private Declare Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Long, ByVal lpString2 As Long) As Long
   Private Declare Function PasteToObj Lib "User32" Alias "SendMessageA" (ByVal hWnd As Long, Optional ByVal wMsg As Long = &H302, Optional ByVal wParam As Long = 0, Optional lParam As Any = 0&) As Long
   
#End If


Public Sub SetClipboard(sUniText$)
#If VBA7 Then
    Dim iStrPtr As LongPtr
    Dim iLock As LongPtr
#Else
    Dim iStrPtr As Long
    Dim iLock As Long
#End If
    Dim iLen As Long
    Const GMEM_MOVEABLE As Long = &H2
    Const GMEM_ZEROINIT As Long = &H40
    Const CF_UNICODETEXT As Long = &HD
    OpenClipboard 0&
    EmptyClipboard
    iLen = LenB(sUniText) + 2&
    iStrPtr = GlobalAlloc(GMEM_MOVEABLE + GMEM_ZEROINIT, iLen)
    iLock = GlobalLock(iStrPtr)
    lstrcpy iLock, StrPtr(sUniText)
    GlobalUnlock iStrPtr
    SetClipboardData CF_UNICODETEXT, iStrPtr
    CloseClipboard
End Sub

Public Function GetClipboard$()
#If VBA7 Then
    Dim iStrPtr As LongPtr
    Dim iLock As LongPtr
#Else
    Dim iStrPtr As Long
    Dim iLock As Long
#End If
    Dim iLen As Long, sUniText$
    Const CF_UNICODETEXT As Long = 13&
    OpenClipboard 0&
    If IsClipboardFormatAvailable(CF_UNICODETEXT) Then
        iStrPtr = GetClipboardData(CF_UNICODETEXT)
        If iStrPtr Then
            iLock = GlobalLock(iStrPtr)
            iLen = GlobalSize(iStrPtr)
            sUniText = String$(iLen \ 2& - 1&, vbNullChar)
            lstrcpy StrPtr(sUniText), iLock
            GlobalUnlock iStrPtr
        End If
        GetClipboard = sUniText
    End If
    CloseClipboard
End Function

출처: https://vbaa2z.blogspot.com/2021/01/working-with-clipboard-api.html

 

Working with Clipboard API

VBA programming, Excel, Access, Microsoft office, VBAA2Z, Lung Pamai, UI UX, Web Scarper VBA,

vbaa2z.blogspot.com

 

 

기타 API 모음:

https://jkp-ads.com/articles/apideclarations.asp

 

Declaring API functions for 64 bit Office (and Mac Office)

Declaring API functions for 64 bit Office (and Mac Office) Content Introduction If you develop VBA code for multiple versions of Office, you may face a challenge: ensuring your code works on both 32 bit and 64 bit platforms. This page is meant to be the fi

jkp-ads.com