ProcessIT Custom Business Software

Custom Software Development for Your Business Needs

VBA Conditional Compilation

How to

Quick link - See our list of conditional compilations below

Vba7 was introduced alongside Office 2010 to support 64 bit versions of Office.

In a 64 bit process a pointer is 64 bits and in a 32 bit process a pointer is 32 bits.

VBA 7.1 introduced

  • The LongLong Type which represents a 64 bit pointer.

  • The LongPtr Type which is treated as a Long in a 32 bit environment and as a LongLong in a 64 bit environment.

  • The PtrSafe Attribute. If your running a 64 bit environment the VBA compiler will generate an error if any Declare statement does not include PtrSafe attribute.

  • The Vba7 conditional compilation argument.

Pre-defined Conditional Constants


Constant 16 bit 32 bit 64 bit
Vba6FalseIf Vba6False
Vba7FalseIf Vba7True
Win16TrueFalseFalse
Win32FalseTrueTrue
Win64FalseFalseTrue
MacFalseIf MacIf Mac

Win64/Win32 refer to the Office version, not the Windows version. For example Win32=TRUE in 32-bit Office, even if the OS is a 64-bit version of Windows.


VBA 6

VBA 6 does not support LongPtr or PtrSafe so any code that is shared between the two environments, VBA 6 to VBA 7, must be conditionally defined.

In order to do this we need to add a conditional compilation block to the top of a module that will house the required Declare statements.

For Example:

#If Vba7 Then
Declare PtrSafe Sub CopyMemoryToVBA Lib "kernel32" _
  Alias "RtlMoveMemory" _
  (ByRef VBALocation As Any, _
  ByVal SourceLoc As LongPtr, _
  ByVal length As Long)
#Else
Declare Sub CopyMemoryToVBA Lib "kernel32" _
  Alias "RtlMoveMemory" _
  (ByRef VBALocation As Any, _
  ByVal SourceLoc As Long, _
  ByVal length As Long)
#End If

This will simply determine if the environment can handle LongPtr or PtrSafe declarations and choose the appropriate Declaration to compile with.

Declare Import Statements to work in all Versions of Office

#If Vba7 Then
  ' It's important to check for Win64 first,
  ' because Win32 will also return true when Win64 does.
  #If Win64 Then
    Declare PtrSafe Function GetFoo64 Lib "exampleLib32" () As LongLong
  #Else
    Declare PtrSafe Function GetFoo Lib "exampleLib32" () As Long
  #End If
#Else
  ' Must be Vba6, the PtrSafe keyword didn't exist back then,
  ' so we need to declare Win32 imports a bit differently than above.
  #If Win32 Then
    Declare Function GetFoo Lib "exampleLib32"() As Long
  #Else '16 bit
    Declare Function GetFoo Lib "exampleLib"() As Integer
  #End If
#End If

If you don't have to support anything older than Office 2010, this declaration works just fine.

' We only have 2010 installs, so we already know we have Vba7.
#If Win64 Then
  Declare PtrSafe Function GetFoo64 Lib "exampleLib32" () As LongLong
#Else
  Declare PtrSafe Function GetFoo Lib "exampleLib32" () As Long
#End If

Microsoft

VBA Conditional Compilation List

Although great care has been used to establish which declarations require longptr variables some may not be correct. Use with some degree of caution.

ProcessIT can alter or update your existing MS Access Solutions. Get your free initial consultation or contact us for more information.

Struggling with a complex query? Not sure why Access behaves in certain ways? Need help pointing you in the right direction? ProcessIT does more than just custom software. ProcessIT can help with your development projects.

32 Bit and ptrsafe 64 Bit Methods

Alphabetised

C

Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hwnd As Long, ByVal msg As Long, ByVal wParam As Long, ByVallParam As Long) As Long

Declare PtrSafe Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As LongPtr, ByVal hwnd As LongPtr, ByVal msg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr


Declare Function CloseClipboard Lib "user32" () As Long

Declare PtrSafe Function CloseClipboard Lib "user32" () As LongPtr


Declare Function CoCreateGuid Lib "ole32" (ByRef Guid As Byte) As Long

Declare PtrSafe Function CoCreateGuid Lib "ole32.dll" (Guid As GUID_TYPE) As LongPtr


Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)

Declare PtrSafe Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, hpvSource As Any, ByVal cbCopy As LongPtr)


Declare Sub CoTaskMemFree Lib "ole32" (ByVal hMem As Long)

Declare PtrSafe Sub CoTaskMemFree Lib "ole32" (ByVal hMem As LongPtr)


D

Declare Function DrawMenuBar Lib "user32" (ByVal hWnd As Long) As Long

Public Declare PtrSafe Function DrawMenuBar Lib "user32" (ByVal hWnd As LongPtr) As Long


E

Declare Function EmptyClipboard Lib "user32" () As Long

Declare PtrSafe Function EmptyClipboard Lib "user32" () As Long


Declare Function EnableMenuItem Lib "user32" (ByVal hMenu As Long, ByVal wIDEnableItem As Long, ByVal wEnable As Long) As Long

Declare PtrSafe Function EnableMenuItem Lib "user32" (ByVal hMenu As LongPtr, ByVal wIDEnableItem As Long, ByVal wEnable As Long) As Long


Declare Function EnumWindows Lib "user32" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long

Declare PtrSafe Function EnumWindows Lib "user32" (ByVal lpEnumFunc As LongPtr, ByVal lParam As LongPtr) As Long


Declare Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As Long, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As Long

Declare PtrSafe Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As LongPtr, ByVal lpszExeFileName As String, ByVal nIconIndex As Long) As LongPtr


F

Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr


Declare Function FindWindowEx Lib "user32Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, _ ByVal lpsz1 As String, ByVal lpsz2 As String) As Long

Declare PtrSafe Function FindWindowEx Lib "USER32" _ Alias "FindWindowExA" (ByVal hWnd1 As LongPtr, ByVal hWnd2 As LongPtr, _ ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPtr


G

Declare Function GdipCreateBitmapFromFile Lib "GDIPlus" (ByVal filename As Long, bitmap As Long) As Long

Private Declare PtrSafe Function GdipCreateBitmapFromFile Lib "GDIPlus" (ByVal filename As LongPtr, bitmap As LongPtr) As LongPtr


Declare Function GdipCreateHBITMAPFromBitmap Lib "GDIPlus" (ByVal bitmap As Long, hbmReturn As Long, ByVal background As Long) As Long

Private Declare PtrSafe Function GdipCreateHBITMAPFromBitmap Lib "GDIPlus" (ByVal bitmap As LongPtr, hbmReturn As LongPtr, ByVal background As Long) As LongPtr


Declare Function GdipDisposeImage Lib "GDIPlus" (ByVal image As Long) As Long

Private Declare PtrSafe Function GdipDisposeImage Lib "GDIPlus" (ByVal image As LongPtr) As LongPtr


Declare Function GdiplusShutdown Lib "GDIPlus" (ByVal token As Long) As Long

Private Declare PtrSafe Function GdiplusShutdown Lib "GDIPlus" (ByVal token As LongPtr) As LongPtr


Declare Function GdiplusStartup Lib "GDIPlus" (token As Long, inputbuf As GdiplusStartupInput, Optional ByVal outputbuf As Long=0) As Long

Private Declare PtrSafe Function GdiplusStartup Lib "GDIPlus" (token As LongPtr, inputbuf As GdiplusStartupInput, Optional ByVal outputbuf As LongPtr=0) As LongPtr


Declare Function GetActiveWindow Lib "user32" () As Long

Declare PtrSafe Function GetActiveWindow Lib "user32" () As Long


Declare Function GetClassName Lib "USER32" Alias "GetClassNameA" (ByVal hWnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) 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


Declare Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As Long

Declare PtrSafe Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongPtr


Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long

Declare PtrSafe Function GetCursorPos Lib "user32" Alias "GetCursorPos" (lpPoint As POINTAPI) As Long


Declare Function GetDiskFreeSpaceEx Lib "kernel32" _ Alias "GetDiskFreeSpaceExA" (ByVal lpDirectoryName As String, _ lpFreeBytesAvailableToCaller As Currency, _ lpTotalNumberOfBytes As Currency, _ lpTotalNumberOfFreeBytes As Currency) As Long

Declare PtrSafe Function GetDiskFreeSpaceEx Lib "kernel32" Alias _ "GetDiskFreeSpaceExA" (ByVal lpDirectoryName As String, _ lpFreeBytesAvailableToCaller As Currency, lpTotalNumberOfBytes As _ Currency, lpTotalNumberOfFreeBytes As Currency) As LongPtr


Declare Function GetFileVersionInfo Lib "version.dll" Alias "GetFileVersionInfoA" (ByVal lptstrFilename As String, ByVal dwHandle As Long, ByVal dwLen As Long, lpData As Any) As Long

Declare PtrSafe Function GetFileVersionInfo Lib "version.dll" Alias "GetFileVersionInfoA" (ByVal lptstrFilename As String, ByVal dwHandle As LongPtr, ByVal dwLen As LongPtr, lpData As Any) As LongPtr


Declare Function GetFileVersionInfoSize Lib "version.dll" Alias "GetFileVersionInfoSizeA" (ByVal lptstrFilename As String, lpdwHandle As Long) As Long

Declare PtrSafe Function GetFileVersionInfoSize Lib "version.dll" Alias "GetFileVersionInfoSizeA" (ByVal lptstrFilename As String, lpdwHandle As LongPtr) As LongPtr


Declare Function GetForegroundWindow Lib "User32.dll" () As Long

Declare PtrSafe Function GetForegroundWindow Lib "User32.dll" () As LongPtr


Declare Function GetIpAddrTable Lib "Iphlpapi" (pIPAdrTable As Byte, pdwSize As Long, ByVal Sort As Long) As Long

Declare PtrSafe Function GetIpAddrTable Lib "Iphlpapi" (pIPAdrTable As Byte, pdwSize As LongPtr, ByVal Sort As LongPtr) As Long


Declare Function GetSystemMenu Lib "user32" (ByVal hwnd As Long, ByVal wRevert As Long) As Long

Declare PtrSafe Function GetSystemMenu Lib "user32" (ByVal hwnd As LongPtr, ByVal bRevert As Long) As LongPtr


Declare Function GetSystemMetrics32 Lib "user32" Alias "GetSystemMetrics" (ByVal nIndex As Long) As Long

Declare PtrSafe Function GetSystemMetrics32 Lib "user32" Alias "GetSystemMetrics" (ByVal nIndex As Long) As Long


Declare Function GetTickCount Lib "Kernel32" () As LongPtr

Declare PtrSafe Function GetTickCount Lib "Kernel32" Alias "GetTickCount64" () As LongPtr


Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Declare PtrSafe Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long


Declare Function GetWindow Lib "user32" (ByVal hWnd As Long, ByVal wCmd As Long) As Long

Declare PtrSafe Function GetWindow Lib "user32" (ByVal hWnd As LongPtr, ByVal wCmd As Long) As LongPtr


Declare Function GetWindowLongPtr Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long

Declare PtrSafe Function GetWindowLongPtr Lib "user32" Alias "GetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As LongPtr


Declare Function GetWindowRect Lib "user32" ( ByVal hwnd As Long, lpRect As RECT) As Long

Declare PtrSafe Function GetWindowRect Lib "user32" (ByVal hwnd As LongPtr, lpRect As RECT) As Long


Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long

Declare PtrSafe Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As LongPtr, ByVal lpString As String, ByVal cch As Long) As Long


Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags&, ByVal dwBytes As Long) As Long

Declare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags&, ByVal dwBytes As LongPtr) As LongPtr


Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long

Declare PtrSafe Function GlobalFree Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr


Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long

Declare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr


Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long

Declare PtrSafe Function GlobalSize Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr


Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long

Declare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr


I

Declare Function InternetGetConnectedStateEx Lib "wininet.dll" (ByRef lpdwFlags As Long, ByVal lpszConnectionName As String, ByVal dwNameLen As Integer, ByVal dwReserved As Long) As Long

Declare PtrSafe Function InternetGetConnectedStateEx Lib "wininet.dll" (ByRef lpdwFlags As LongPtr, ByVal lpszConnectionName As String, ByVal dwNameLen As Integer, ByVal dwReserved As Long) As Long


Declare Function IsWindowVisible Lib "user32" (ByVal hWnd As Long) As Long

Declare PtrSafe Function IsWindowVisible Lib "user32" (ByVal hWnd As LongPtr) As LongPtr


L

Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long

Declare PtrSafe Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As LongPtr


Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As String) As Long

Declare PtrSafe Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As String) As LongPtr


M

Declare Function MultiByteToWideChar Lib "kernel32" (ByVal CodePage As Long, ByVal dwFlags As Long, lpMultiByteStr As Any, ByVal cchMultiByte As Long, ByVal lpWideCharStr As Long, ByVal cchWideChar As Long) As Long

Declare PtrSafe Function MultiByteToWideChar Lib "kernel32" (ByVal CodePage As Long, ByVal dwFlags As Long, ByVal lpMultiByteStr As String, ByVal cchMultiByte As Long, ByVal lpWideCharStr As String, ByVal cchWideChar As Long) As Long


O

Declare Function OpenClipboard Lib "user32" (ByVal hWnd As Long) As Long

Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hWnd As LongPtr) As LongPtr


Declare Function OpenIcon Lib "user32" Alias "OpenIcon" (ByVal hwnd As Long) As Long

Declare PtrSafe Function OpenIcon Lib "user32" Alias "OpenIcon" (ByVal hwnd As LongPtr) As Long


S

Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long

Declare PtrSafe Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As LongPtr, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long


Declare Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As Long) As Long

Declare PtrSafe Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As LongPtr) As LongPtr


Declare Function SetCursorPos Lib "user32" (ByVal x As Long, ByVal y As Long) As Long

Declare PtrSafe Function SetCursorPos Lib "user32" (ByVal x As Long, ByVal y As Long) as Long


Declare Function SetForegroundWindow Lib "user32" (ByVal hwnd As Long) As Long

Declare PtrSafe Function SetForegroundWindow Lib "user32" (ByVal hwnd As LongPtr) As Long


Declare Function SetWindowLongPtr Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long

Declare PtrSafe Function SetWindowLongPtr Lib "user32" Alias "SetWindowLongPtrA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr


Declare Function SHBrowseForFolder Lib "shell32.dll" Alias "SHBrowseForFolderA" (lpBrowseInfo As BROWSEINFO) As Long

Declare PtrSafe Function SHBrowseForFolder Lib "shell32.dll" Alias "SHBrowseForFolderA" (lpBrowseInfo As BROWSEINFO) As LongPtr


Declare Function Shell_NotifyIcon Lib "shell32.dll" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As Long

Declare PtrSafe Function Shell_NotifyIcon Lib "shell32.dll" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As LongPtr


Declare Function SHGetFileInfo Lib "shell32.dll" Alias "SHGetFileInfoA" (ByVal pszPath As String, ByVal dwFileAttributes As Long, psfi As SHFILEINFO, ByVal cbSizeFileInfo As Long, ByVal uFlags As Long) As Long

Declare PtrSafe Function SHGetFileInfo Lib "shell32.dll" Alias "SHGetFileInfoA" (ByVal pszPath As String, ByVal dwFileAttributes As Long, psfi As SHFILEINFO, ByVal cbFileInfo As Long, ByVal uFlags As Long) As LongPtr

Declare Function SHGetPathFromIDList Lib "shell32.dll" Alias "SHGetPathFromIDListA" (ByVal pidl As Long, ByVal pszPath As String) As Long

Declare PtrSafe Function SHGetPathFromIDList Lib "shell32.dll" Alias "SHGetPathFromIDListA" (ByVal pidl As LongPtr, ByVal pszPath As String) As Long


Declare Function ShowWindow Lib "user32" Alias "ShowWindow" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long

Declare PtrSafe Function ShowWindow Lib "user32" Alias "ShowWindow" (ByVal hwnd As LongPtr, ByVal nCmdShow As Long) As Long


V

Declare Function VerQueryValue Lib "version.dll" Alias "VerQueryValueA" (pBlock As Any, ByVal lpSubBlock As String, lpBuffer As Any, nVerSize As Long) As Long

Declare PtrSafe Function VerQueryValue Lib "version.dll" Alias "VerQueryValueA" (pBlock As Any, ByVal lpSubBlock As String, lpBuffer As Any, nVerSize As LongPtr) As LongPtr


W

Declare Function WideCharToMultiByte Lib "kernel32" (ByVal CodePage As Long, ByVal dwFlags As Long, ByVal lpWideCharStr As Long, ByVal cchWideChar As Long, lpMultiByteStr As Any, ByVal cchMultiByte As Long, ByVal lpDefaultChar As Long, ByVal lpUsedDefaultChar As Long) As Long

Declare PtrSafe Function WideCharToMultiByte Lib "kernel32" Alias "WideCharToMultiByte" (ByVal CodePage As Long, ByVal dwFlags As Long, ByVal lpWideCharStr As String, ByVal cchWideChar As Long, ByVal lpMultiByteStr As String, ByVal cchMultiByte As Long, ByVal lpDefaultChar As String, ByVal lpUsedDefaultChar As LongPtr) As Long


Declare Sub wlib_AccColorDialog Lib "msaccess.exe" Alias "#53" (ByVal hwnd As Long, lngRGB As Long)

Declare PtrSafe Sub wlib_AccColorDialog Lib "msaccess.exe" Alias "#53" (ByVal hwnd As LongPtr, lngRGB As Long)


Object Types

Type BROWSEINFO
 hOwner As Long
 pidlRoot As Long
 pszDisplayName As String
 lpszTitle As String
 ulFlags As Long
 lpfn As Long
 lParam As Long
 iImage As Long
End Type

Type BROWSEINFO
 hOwner As LongPtr
 pidlRoot As LongPtr
 pszDisplayName As String
 lpszTitle As String
 ulFlags As Long
 lpfn As LongPtr
 lParam As LongPtr
 iImage As Long
End Type


Type FindWindowParameters
 strTitle As String 'INPUT
 hWnd As Long 'OUTPUT
End Type

Type FindWindowParameters
 strTitle As String 'INPUT
 hWnd As LongPtr 'OUTPUT
End Type


Type GdiplusStartupInput
 GdiplusVersion As Long
 DebugEventCallback As Long
 SuppressBackgroundThread As Long
 SuppressExternalCodecs As Long
End Type

Type GdiplusStartupInput
 GdiplusVersion As Long
 DebugEventCallback As LongPtr
 SuppressBackgroundThread As Long
 SuppressExternalCodecs As Long
End Type


Identical 32 vs 64
Type GUID_TYPE
 Data1 As Long
 Data2 As Integer
 Data3 As Integer
 Data4(7) As Byte
End Type


Type OPENFILENAME
 lStructSize As Long
 hwndOwner As Long
 hLeads_User As Long
 lpstrFilter As String
 lpstrCustomFilter As String
 nMaxCustFilter As Long
 iFilterIndex As Long
 lpstrFile As String
 nMaxFile As Long
 lpstrFileTitle As String
 nMaxFileTitle As Long
 lpstrInitialDir As String
 lpstrTitle As String
 Flags As Long
 nFileOffset As Integer
 nFileExtension As Integer
 lpstrDefExt As String
 lCustData As Long
 lpfnHook As Long
 lpTemplateName As String
End Type

Type OPENFILENAME
 lStructSize As Long
 hwndOwner As LongPtr
 hInstance As LongPtr
 lpstrFilter As String
 lpstrCustomFilter As Long
 nMaxCustrFilter As Long
 nFilterIndex As Long
 lpstrFile As String
 nMaxFile As Long
 lpstrFileTitle As String
 nMaxFileTitle As Long
 lpstrInitialDir As String
 lpstrTitle As String
 Flags As Long
 nFileOffset As Integer
 nFileExtension As Integer
 lpstrDefExt As String
 lCustrData As LongPtr
 lpfnHook As LongPtr
 lpTemplateName As Long
End Type


Identical 32 vs 64
Type OSVERSIONINFO
 dwOSVersionInfoSize As Long
 dwMajorVersion As Long
 dwMinorVersion As Long
 dwBuildNumber As Long
 dwPlatformId As Long
 szCSDVersion As String * 128
End Type


Type POINTAPI
 X_Pos As Long
 Y_Pos As Long
End Type

Type POINTAPI
 X_Pos As Long
 Y_Pos As Long
End Type


Type SHFILEINFO
 hIcon As Long
 iIcon As Long
 dwAttributes As Long
 szDisplayName As String * MAX_PATH
 szTypeName As String * 80
End Type

Type SHFILEINFO
 hIcon As LongPtr
 iIcon As Long
 dwAttributes As Long
 szDisplayName As String * MAX_PATH
 szTypeName As String * 80
End Type