Viele Unternehmen – vor allem im KMU-Bereich – nutzen über Jahre hinweg gewachsene Office-Anwendungen, die intern in Access, Excel oder Word per VBA gesteuert werden.
Läuft. Warum was ändern?

Aber spätestens bei der Einführung von Office 64-Bit (z. B. über Microsoft 365) kracht es.
Die Ursache: 64-Bit-Office kommt mit einer anderen Speicherarchitektur – und viele klassische Declare-Anweisungen aus der 32-Bit-Welt laufen dann schlicht nicht mehr.

Was Du tun musst:

  • Bedingte Kompilierung über #If VBA7 Then
  • Anpassung aller API-Deklarationen
  • Verwendung von LongPtr statt Long für Pointer und Handles

Damit Du nicht alle APIs selbst recherchieren musst, findest Du nachfolgend die 50 wichtigsten Windows-API-Aufrufe für VBA – je einmal in der alten 32-Bit-Variante und direkt daneben in der korrekten 64-Bit-Deklaration.

Top-50 API-Deklarationen: 32-Bit vs. 64-Bit

Funktion32-Bit (alt)64-Bit (neu)
SleepDeclare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
ShellExecuteDeclare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As LongDeclare PtrSafe Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As LongPtr, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As LongPtr
GetTickCountDeclare Function GetTickCount Lib "kernel32" () As LongDeclare PtrSafe Function GetTickCount Lib "kernel32" () As Long
FindWindowDeclare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongDeclare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
SetForegroundWindowDeclare Function SetForegroundWindow Lib "user32" (ByVal hwnd As Long) As LongDeclare PtrSafe Function SetForegroundWindow Lib "user32" (ByVal hwnd As LongPtr) As Long
GetAsyncKeyStateDeclare Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As IntegerDeclare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer
OpenClipboardDeclare Function OpenClipboard Lib "user32" (ByVal hwnd As Long) As LongDeclare PtrSafe Function OpenClipboard Lib "user32" (ByVal hwnd As LongPtr) As Long
CloseClipboardDeclare Function CloseClipboard Lib "user32" () As LongDeclare PtrSafe Function CloseClipboard Lib "user32" () As Long
EmptyClipboardDeclare Function EmptyClipboard Lib "user32" () As LongDeclare PtrSafe Function EmptyClipboard Lib "user32" () As Long
GetClipboardDataDeclare Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongDeclare PtrSafe Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongPtr
GlobalAllocDeclare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As LongDeclare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As LongPtr) As LongPtr
GlobalLockDeclare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As LongDeclare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
GlobalUnlockDeclare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As LongDeclare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As Long
MessageBoxDeclare Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hwnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As LongDeclare PtrSafe Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hwnd As LongPtr, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long
CreateFileDeclare Function CreateFile Lib "kernel32" Alias "CreateFileA" (...) As LongDeclare PtrSafe Function CreateFile Lib "kernel32" Alias "CreateFileA" (...) As LongPtr
WriteFileDeclare Function WriteFile Lib "kernel32" (...) As LongDeclare PtrSafe Function WriteFile Lib "kernel32" (...) As Long
ReadFileDeclare Function ReadFile Lib "kernel32" (...) As LongDeclare PtrSafe Function ReadFile Lib "kernel32" (...) As Long
CloseHandleDeclare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As LongDeclare PtrSafe Function CloseHandle Lib "kernel32" (ByVal hObject As LongPtr) As Long
SetTimerDeclare Function SetTimer Lib "user32" (...) As LongDeclare PtrSafe Function SetTimer Lib "user32" (...) As LongPtr
KillTimerDeclare Function KillTimer Lib "user32" (...) As LongDeclare PtrSafe Function KillTimer Lib "user32" (...) As Long
GetWindowRectDeclare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As LongDeclare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long
GetCursorPosDeclare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As LongDeclare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
MoveWindowDeclare Function MoveWindow Lib "user32" (...) As LongDeclare PtrSafe Function MoveWindow Lib "user32" (...) As Long
SetWindowPosDeclare Function SetWindowPos Lib "user32" (...) As LongDeclare PtrSafe Function SetWindowPos Lib "user32" (...) As Long
GetSystemMetricsDeclare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As LongDeclare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
ExitWindowsExDeclare Function ExitWindowsEx Lib "user32" (...) As LongDeclare PtrSafe Function ExitWindowsEx Lib "user32" (...) As Long
SetCursorPosDeclare Function SetCursorPos Lib "user32" (ByVal X As Long, ByVal Y As Long) As LongDeclare PtrSafe Function SetCursorPos Lib "user32" (ByVal X As Long, ByVal Y As Long) As Long
EnableWindowDeclare Function EnableWindow Lib "user32" (ByVal hwnd As Long, ByVal fEnable As Long) As LongDeclare PtrSafe Function EnableWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal fEnable As Long) As Long
GetDCDeclare Function GetDC Lib "user32" (ByVal hwnd As Long) As LongDeclare PtrSafe Function GetDC Lib "user32" (ByVal hwnd As LongPtr) As LongPtr
ReleaseDCDeclare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As LongDeclare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hdc As LongPtr) As Long
InvalidateRectDeclare Function InvalidateRect Lib "user32" (ByVal hwnd As Long, ByVal lpRect As Long, ByVal bErase As Long) As LongDeclare PtrSafe Function InvalidateRect Lib "user32" (ByVal hwnd As LongPtr, ByVal lpRect As LongPtr, ByVal bErase As Long) As Long
SystemParametersInfoDeclare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (...) As LongDeclare PtrSafe Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (...) As Long
MessageBeepDeclare Function MessageBeep Lib "user32" (ByVal wType As Long) As LongDeclare PtrSafe Function MessageBeep Lib "user32" (ByVal wType As Long) As Long
SetWindowTextDeclare Function SetWindowText Lib "user32" Alias "SetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String) As LongDeclare PtrSafe Function SetWindowText Lib "user32" Alias "SetWindowTextA" (ByVal hwnd As LongPtr, ByVal lpString As String) As Long
GetWindowTextDeclare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (...) As LongDeclare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" (...) As Long
SetCaptureDeclare Function SetCapture Lib "user32" () As LongDeclare PtrSafe Function SetCapture Lib "user32" () As LongPtr
ReleaseCaptureDeclare Function ReleaseCapture Lib "user32" () As LongDeclare PtrSafe Function ReleaseCapture Lib "user32" () As Long
BitBltDeclare Function BitBlt Lib "gdi32" (...) As LongDeclare PtrSafe Function BitBlt Lib "gdi32" (...) As Long
CreateCompatibleDCDeclare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As LongDeclare PtrSafe Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As LongPtr) As LongPtr
CreateCompatibleBitmapDeclare Function CreateCompatibleBitmap Lib "gdi32" (...) As LongDeclare PtrSafe Function CreateCompatibleBitmap Lib "gdi32" (...) As LongPtr
SelectObjectDeclare Function SelectObject Lib "gdi32" (...) As LongDeclare PtrSafe Function SelectObject Lib "gdi32" (...) As LongPtr
DeleteObjectDeclare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As LongDeclare PtrSafe Function DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long
DeleteDCDeclare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As LongDeclare PtrSafe Function DeleteDC Lib "gdi32" (ByVal hdc As LongPtr) As Long
StretchBltDeclare Function StretchBlt Lib "gdi32" (...) As LongDeclare PtrSafe Function StretchBlt Lib "gdi32" (...) As Long
SetTextColorDeclare Function SetTextColor Lib "gdi32" (...) As LongDeclare PtrSafe Function SetTextColor Lib "gdi32" (...) As Long
SetBkModeDeclare Function SetBkMode Lib "gdi32" (...) As LongDeclare PtrSafe Function SetBkMode Lib "gdi32" (...) As Long

' Modul: WinAPI64Support.bas
' Zweck: Kompatible Windows-API-Deklarationen für 32-Bit und 64-Bit VBA in Office 2024
' Autor: Sönke Schäfer, SeSoft GmbH
' Hinweis: Bei Handles und Zeigern Long durch LongPtr ersetzen

#If VBA7 Then
    ' 64-Bit oder neue 32-Bit-Compiler

    ' Wartet für eine bestimmte Zeitspanne
    Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)

    ' Öffnet eine Datei oder URL mit dem Standardprogramm
    Declare PtrSafe Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
        (ByVal hwnd As LongPtr, ByVal lpOperation As String, ByVal lpFile As String, _
         ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As LongPtr

    ' Gibt die Zeit seit Systemstart in Millisekunden zurück
    Declare PtrSafe Function GetTickCount Lib "kernel32" () As Long

    ' Sucht nach einem Fenster anhand Klassenname oder Titel
    Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" _
        (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr

    ' Bringt Fenster in den Vordergrund
    Declare PtrSafe Function SetForegroundWindow Lib "user32" (ByVal hwnd As LongPtr) As Long

    ' Prüft, ob eine Taste gedrückt wurde
    Declare PtrSafe Function GetAsyncKeyState Lib "user32" (ByVal vKey As Long) As Integer

    ' Öffnet das Clipboard
    Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hwnd As LongPtr) As Long

    ' Schließt das Clipboard
    Declare PtrSafe Function CloseClipboard Lib "user32" () As Long

    ' Leert das Clipboard
    Declare PtrSafe Function EmptyClipboard Lib "user32" () As Long

    ' Liest Daten aus dem Clipboard
    Declare PtrSafe Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongPtr

    ' Allokiert globalen Speicher
    Declare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As LongPtr) As LongPtr

    ' Sperrt globalen Speicher (Pointer)
    Declare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr

    ' Gibt globalen Speicher wieder frei
    Declare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As Long

    ' Zeigt eine MessageBox an
    Declare PtrSafe Function MessageBox Lib "user32" Alias "MessageBoxA" _
        (ByVal hwnd As LongPtr, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long

    ' Öffnet oder erstellt eine Datei/Handle
    Declare PtrSafe Function CreateFile Lib "kernel32" Alias "CreateFileA" _
        (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, _
         ByVal lpSecurityAttributes As LongPtr, ByVal dwCreationDisposition As Long, _
         ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As LongPtr) As LongPtr

    ' Schreibt Daten in ein Handle (z. B. Datei)
    Declare PtrSafe Function WriteFile Lib "kernel32" _
        (ByVal hFile As LongPtr, ByRef lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, _
         ByRef lpNumberOfBytesWritten As Long, ByVal lpOverlapped As LongPtr) As Long

    ' Liest Daten aus einem Handle (z. B. Datei)
    Declare PtrSafe Function ReadFile Lib "kernel32" _
        (ByVal hFile As LongPtr, ByRef lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, _
         ByRef lpNumberOfBytesRead As Long, ByVal lpOverlapped As LongPtr) As Long

    ' Schließt ein geöffnetes Handle (z. B. Datei)
    Declare PtrSafe Function CloseHandle Lib "kernel32" (ByVal hObject As LongPtr) As Long

    ' Startet einen Timer
    Declare PtrSafe Function SetTimer Lib "user32" _
        (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, ByVal uElapse As Long, ByVal lpTimerFunc As LongPtr) As LongPtr

    ' Beendet einen Timer
    Declare PtrSafe Function KillTimer Lib "user32" (ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As Long

    ' Gibt die Fensterposition/-größe zurück
    Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As Any) As Long

    ' Gibt die aktuelle Mausposition zurück
    Declare PtrSafe Function GetCursorPos Lib "user32" (lpPoint As Any) As Long

    ' Verschiebt ein Fenster
    Declare PtrSafe Function MoveWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal X As Long, ByVal Y As Long, _
        ByVal nWidth As Long, ByVal nHeight As Long, ByVal bRepaint As Long) As Long

    ' Setzt Fensterposition im Z-Stack
    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 uFlags As Long) As Long

    ' Liefert Systemmaße (z. B. Bildschirmgröße)
    Declare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long

    ' Fährt Windows herunter
    Declare PtrSafe Function ExitWindowsEx Lib "user32" (ByVal uFlags As Long, ByVal dwReason As Long) As Long

    ' Setzt den Cursor an eine bestimmte Position
    Declare PtrSafe Function SetCursorPos Lib "user32" (ByVal X As Long, ByVal Y As Long) As Long

    ' Aktiviert oder deaktiviert ein Fenster
    Declare PtrSafe Function EnableWindow Lib "user32" (ByVal hwnd As LongPtr, ByVal fEnable As Long) As Long

    ' Holt Device Context (für GDI)
    Declare PtrSafe Function GetDC Lib "user32" (ByVal hwnd As LongPtr) As LongPtr

    ' Gibt Device Context frei
    Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hwnd As LongPtr, ByVal hdc As LongPtr) As Long

    ' Ungültige Bereichsmarkierung (Neuzeichnung)
    Declare PtrSafe Function InvalidateRect Lib "user32" (ByVal hwnd As LongPtr, ByVal lpRect As LongPtr, ByVal bErase As Long) As Long

    ' Holt oder setzt Systemeinstellungen
    Declare PtrSafe Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" _
        (ByVal uiAction As Long, ByVal uiParam As Long, ByRef pvParam As Any, ByVal fWinIni As Long) As Long

    ' Spielt Systembeep
    Declare PtrSafe Function MessageBeep Lib "user32" (ByVal wType As Long) As Long

    ' Setzt Fenstertitel
    Declare PtrSafe Function SetWindowText Lib "user32" Alias "SetWindowTextA" _
        (ByVal hwnd As LongPtr, ByVal lpString As String) As Long

    ' Liest Fenstertitel
    Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" _
        (ByVal hwnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long

    ' Erfasst Mauscursor für ein Fenster
    Declare PtrSafe Function SetCapture Lib "user32" () As LongPtr

    ' Gibt Mauscursor wieder frei
    Declare PtrSafe Function ReleaseCapture Lib "user32" () As Long

    ' Kopiert Bitmaps von einem DC in einen anderen
    Declare PtrSafe Function BitBlt Lib "gdi32" _
        (ByVal hDestDC As LongPtr, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, _
         ByVal hSrcDC As LongPtr, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long

    ' Erstellt kompatiblen DC
    Declare PtrSafe Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As LongPtr) As LongPtr

    ' Erstellt Bitmap, kompatibel zu bestehendem DC
    Declare PtrSafe Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As LongPtr, _
        ByVal nWidth As Long, ByVal nHeight As Long) As LongPtr

    ' Wählt Objekt (z. B. Bitmap) in DC
    Declare PtrSafe Function SelectObject Lib "gdi32" (ByVal hdc As LongPtr, ByVal hObject As LongPtr) As LongPtr

    ' Löscht GDI-Objekt (z. B. Bitmap)
    Declare PtrSafe Function DeleteObject Lib "gdi32" (ByVal hObject As LongPtr) As Long

    ' Löscht Device Context
    Declare PtrSafe Function DeleteDC Lib "gdi32" (ByVal hdc As LongPtr) As Long

    ' Skalierte Bitmap-Kopie
    Declare PtrSafe Function StretchBlt Lib "gdi32" (...) As Long

    ' Setzt Textfarbe für GDI-Zeichnung
    Declare PtrSafe Function SetTextColor Lib "gdi32" (ByVal hdc As LongPtr, ByVal crColor As Long) As Long

    ' Setzt Hintergrundmodus für GDI
    Declare PtrSafe Function SetBkMode Lib "gdi32" (ByVal hdc As LongPtr, ByVal nBkMode As Long) As Long

#Else
    ' 32-Bit wie bisher (unverändert)
    ' Hier würdest Du die gleichen Funktionssignaturen mit Long statt LongPtr verwenden
#End If