Function name |
Declarations (32 bit followed by 64 bit) |
CreateProcess |
We start off with a complicated one because it has a lot of arguments. A fully functional example is included below the example declaration lines.
Courtesy: The example code was taken from this page
Declare Function CreateProcess Lib “kernel32″ _
Alias “CreateProcessA” ( ByVal lpApplicationName As String, _
ByVal lpCommandLine As String, _
lpProcessAttributes As SECURITY_ATTRIBUTES, _
lpThreadAttributes As SECURITY_ATTRIBUTES, _
ByVal bInheritHandles As Long, _
ByVal dwCreationFlags As Long, _
lpEnvironment As Any, _
ByVal lpCurrentDriectory As String, _
lpStartupInfo As STARTUPINFO, _
lpProcessInformation As PROCESS_INFORMATION) As LongDeclare PtrSafe Function CreateProcess Lib “kernel32″ _
Alias “CreateProcessA” ( ByVal lpApplicationName As String, _
ByVal lpCommandLine As String, _
lpProcessAttributes As SECURITY_ATTRIBUTES, _
lpThreadAttributes As SECURITY_ATTRIBUTES, _
ByVal bInheritHandles As Long, _
ByVal dwCreationFlags As Long, _
lpEnvironment As Any, _
ByVal lpCurrentDriectory As String, _
lpStartupInfo As STARTUPINFO, _
lpProcessInformation As PROCESS_INFORMATION) As LongPtr
‘Full example shown below, including the necessary structures
#If VBA7 Then
Declare PtrSafe Function CreateProcess Lib “kernel32″ _
Alias “CreateProcessA” ( ByVal lpApplicationName As String, _
ByVal lpCommandLine As String, _
lpProcessAttributes As SECURITY_ATTRIBUTES, _
lpThreadAttributes As SECURITY_ATTRIBUTES, _
ByVal bInheritHandles As Long, _
ByVal dwCreationFlags As Long, _
lpEnvironment As Any, _
ByVal lpCurrentDriectory As String, _
lpStartupInfo As STARTUPINFO, _
lpProcessInformation As PROCESS_INFORMATION) As LongPtr Const INFINITE = &HFFFF
Const STARTF_USESHOWWINDOW = &H1
Private Enum enSW
SW_HIDE = 0
SW_NORMAL = 1
SW_MAXIMIZE = 3
SW_MINIMIZE = 6
End EnumPrivate Type PROCESS_INFORMATION
hProcess As LongPtr
hThread As LongPtr
dwProcessId As Long
dwThreadId As Long
End Type
Private Type STARTUPINFO
cb As Long
lpReserved As String
lpDesktop As String
lpTitle As String
dwX As Long
dwY As Long
dwXSize As Long
dwYSize As Long
dwXCountChars As Long
dwYCountChars As Long
dwFillAttribute As Long
dwFlags As Long
wShowWindow As Integer
cbReserved2 As Integer
lpReserved2 As Byte
hStdInput As LongPtr
hStdOutput As LongPtr
hStdError As LongPtr
End Type
Private Type SECURITY_ATTRIBUTES
nLength As Long
lpSecurityDescriptor As LongPtr
bInheritHandle As Long
End Type
Private Enum enPriority_Class
NORMAL_PRIORITY_CLASS = &H20
IDLE_PRIORITY_CLASS = &H40
HIGH_PRIORITY_CLASS = &H80
End Enum
#Else
Declare Function CreateProcess Lib “kernel32″ _
Alias “CreateProcessA” (ByVal lpApplicationName As String, _
ByVal lpCommandLine As String, _
lpProcessAttributes As SECURITY_ATTRIBUTES, _
lpThreadAttributes As SECURITY_ATTRIBUTES, _
ByVal bInheritHandles As Long, _
ByVal dwCreationFlags As Long, _
lpEnvironment As Any, _
ByVal lpCurrentDriectory As String, _
lpStartupInfo As STARTUPINFO, _
lpProcessInformation As PROCESS_INFORMATION)As Long
Const INFINITE = &HFFFF
Const STARTF_USESHOWWINDOW = &H1
Private Enum enSW
SW_HIDE = 0
SW_NORMAL = 1
SW_MAXIMIZE = 3
SW_MINIMIZE = 6
End Enum
Private Type PROCESS_INFORMATION
hProcess As Long
hThread As Long
dwProcessId As Long
dwThreadId As Long
End Type
Private Type STARTUPINFO
cb As Long
lpReserved As String
lpDesktop As String
lpTitle As String
dwX As Long
dwY As Long
dwXSize As Long
dwYSize As Long
dwXCountChars As Long
dwYCountChars As Long
dwFillAttribute As Long
dwFlags As Long
wShowWindow As Integer
cbReserved2 As Integer
lpReserved2 As Byte
hStdInput As Long
hStdOutput As Long
hStdError As Long
End Type
Private Type SECURITY_ATTRIBUTES
nLength As Long
lpSecurityDescriptor As Long
bInheritHandle As Long
End Type
Private Enum enPriority_Class
NORMAL_PRIORITY_CLASS = &H20
IDLE_PRIORITY_CLASS = &H40
HIGH_PRIORITY_CLASS = &H80
End Enum
#End If
Private Function SuperShell(ByVal App As String, ByVal WorkDir As String, dwMilliseconds As Long, _
ByVal start_size As enSW, ByVal Priority_Class As enPriority_Class) AsBoolean
Dim pclass As Long
Dim sinfo As STARTUPINFO
Dim pinfo As PROCESS_INFORMATION
‘Not used, but needed
Dim sec1 As SECURITY_ATTRIBUTES
Dim sec2 As SECURITY_ATTRIBUTES
‘Set the structure size
sec1.nLength = Len(sec1)
sec2.nLength = Len(sec2)
sinfo.cb = Len(sinfo)
‘Set the flags
sinfo.dwFlags = STARTF_USESHOWWINDOW
‘Set the window’s startup position
sinfo.wShowWindow = start_size
‘Set the priority class
pclass = Priority_Class
‘Start the program
If CreateProcess(vbNullString, App, sec1, sec2, False, pclass, _
0&, WorkDir, sinfo, pinfo) Then
‘Wait
‘ WaitForSingleObject pinfo.hProcess, dwMilliseconds
SuperShell = True
Else
SuperShell = False
End If
End Function
Sub Test()
Dim sFile As String
‘Set the dialog’s title
sFile = Application.GetOpenFilename(“Executables (*.exe), *.exe”, , “”)
SuperShell sFile, Left(sFile, InStrRev(sFile, “\”)), 0, SW_NORMAL, HIGH_PRIORITY_CLASS
End Sub
|
FindWindow |
Private Declare Function FindWindow Lib “USER32″ Alias “FindWindowA” (ByVal lpClassName As String, ByVallpWindowName As String) As Long
Private Declare PtrSafe Function FindWindow Lib “USER32″ Alias “FindWindowA” (ByVal lpClassName AsString, ByVal lpWindowName As String) As LongPtr
|
FindWindowEx |
Private Declare Function FindWindowEx Lib “USER32″ _
Alias “FindWindowExA” (ByVal hWnd1 As Long, ByVal hWnd2 As Long, _
ByVal lpsz1 As String, ByVal lpsz2 As String) As LongPrivateDeclare 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
|
GdipCreateBitmapFromFile |
Private 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
|
GdipCreateHBITMAPFromBitmap |
Private Declare Function GdipCreateHBITMAPFromBitmap Lib “GDIPlus” (ByVal bitmap As Long, hbmReturn AsLong, 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
|
GdipDisposeImage |
Private Declare Function GdipDisposeImage Lib “GDIPlus” (ByVal image As Long) As Long
Private Declare PtrSafe Function GdipDisposeImage Lib “GDIPlus” (ByVal image As LongPtr) As LongPtr
|
GdiplusShutdown |
Private Declare Function GdiplusShutdown Lib “GDIPlus” (ByVal token As Long) As Long
Private Declare PtrSafe Function GdiplusShutdown Lib “GDIPlus” (ByVal token As LongPtr) As LongPtr
|
GdiplusStartup |
Private Declare Function GdiplusStartup Lib “GDIPlus” (token As Long, inputbuf As GdiplusStartupInput,Optional ByVal outputbuf As Long = 0) As Long
Private Type GdiplusStartupInput
GdiplusVersion As Long
DebugEventCallback As Long
SuppressBackgroundThread As Long
SuppressExternalCodecs As Long
End Type
Private Declare PtrSafe Function GdiplusStartup Lib “GDIPlus” (token As LongPtr, inputbuf AsGdiplusStartupInput, Optional ByVal outputbuf As LongPtr = 0) As LongPtrPrivate Type GdiplusStartupInput
GdiplusVersion As Long
DebugEventCallback As LongPtr
SuppressBackgroundThread As Long
SuppressExternalCodecs As Long
End Type
|
GetClassName |
Public Declare Function GetClassName Lib “USER32″ Alias “GetClassNameA” _
(ByVal hWnd As Long, ByVal lpClassName As String, _
ByVal nMaxCount As Long) As LongPublic Declare PtrSafe Function GetClassName Lib “USER32″ Alias “GetClassNameA” _
(ByVal hWnd As LongPtr, ByVal lpClassName As String, _
ByVal nMaxCount As LongPtr) As Long
|
GetDiskFreeSpaceEx |
Private Declare Function GetDiskFreeSpaceEx Lib “kernel32″ _
Alias “GetDiskFreeSpaceExA” (ByVal lpDirectoryName As String, _
lpFreeBytesAvailableToCaller As Currency, _
lpTotalNumberOfBytes As Currency, _
lpTotalNumberOfFreeBytes As Currency) As Long
Private Declare PtrSafe Function GetDiskFreeSpaceEx Lib “kernel32″ Alias _
“GetDiskFreeSpaceExA” (ByVal lpDirectoryName As String, _
lpFreeBytesAvailableToCaller As Currency, lpTotalNumberOfBytes As _
Currency, lpTotalNumberOfFreeBytes As Currency) As LongPtr
|
getDC |
Private Declare Function GetDC Lib “USER32″ (ByVal hWnd As Long) As Long
Private Declare PtrSafe Function GetDC Lib “USER32″ (ByVal hWnd As LongPtr) As LongPtr
|
GetDesktopWindow |
Public Declare Function GetDesktopWindow Lib “USER32″ () As LongPublic Declare PtrSafe Function GetDesktopWindow Lib “USER32″ () As LongPtr
|
getDeviceCaps |
Private Declare Function GetDeviceCaps Lib “gdi32″ (ByVal hDC As Long, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetDeviceCaps Lib “gdi32″ (ByVal hDC As LongPtr, ByVal nIndex As Long)As Long
|
GetDriveType |
Private Declare Function GetDriveType Lib “kernel32″ Alias _
“GetDriveTypeA” (ByVal sDrive As String) As LongPrivate Declare PtrSafe Function GetDriveType Lib “kernel32″ Alias _
“GetDriveTypeA” (ByVal sDrive As String) As LongPtr
|
GetExitCodeProcess |
#If VBA7 Then
Declare PtrSafe Function GetExitCodeProcess Lib “kernel32″ (ByVal _
hProcess As LongPtr, lpExitCode As Long) As Long
#Else
Declare Function GetExitCodeProcess Lib “kernel32″ (ByVal _
hProcess As Long, lpExitCode As Long) As Long
#End If
|
GetForegroundWindow |
Declare Function GetForegroundWindow Lib “user32.dll” () As LongDeclare PtrSafe Function GetForegroundWindow Lib “user32.dll” () As LongPtr
|
getFrequency |
Declare Function getFrequency Lib “kernel32″ Alias “QueryPerformanceFrequency” (cyFrequency As Currency)As Long
Private Declare PtrSafe Function getFrequency Lib “kernel32″ Alias “QueryPerformanceFrequency” (cyFrequency As Currency) As Long
|
GetKeyState |
Declare Function GetKeyState Lib “USER32″ (ByVal vKey As Long) As Integer
Declare PtrSafe Function GetKeyState Lib “USER32″ (ByVal vKey As Long) As Integer
|
GetLastInputInfo |
#If VBA7 Then
Private Type LASTINPUTINFO
cbSize As LongPtr
dwTime As LongPtr
End Type
Private Declare PtrSafe Sub GetLastInputInfo Lib “USER32″ (ByRef plii As LASTINPUTINFO)
#Else
Private Type LASTINPUTINFO
cbSize As Long
dwTime As Long
End Type
Private Declare Sub GetLastInputInfo Lib “USER32″ (ByRef plii As LASTINPUTINFO)
#End If
|
GetOpenFileName |
Option Explicit#If VBA7 Then
Public Declare PtrSafe Function GetOpenFileName Lib “comdlg32.dll” Alias _
“GetOpenFileNameA” (pOpenfilename As OPENFILENAME) As LongPublic Type OPENFILENAME
lStructSize As Long
hwndOwner As LongPtr
hInstance As LongPtr
lpstrFilter As String
lpstrCustomFilter As String
nMaxCustFilter 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
lCustData As Long
lpfnHook As LongPtr
lpTemplateName As String
End Type#Else
Public Declare Function GetOpenFileName Lib “comdlg32.dll” Alias _
“GetOpenFileNameA” (pOpenfilename As OPENFILENAME) As Long
Public Type OPENFILENAME
lStructSize As Long
hwndOwner As Long
hInstance As Long
lpstrFilter As String
lpstrCustomFilter As String
nMaxCustFilter 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
lCustData As Long
lpfnHook As Long
lpTemplateName As String
End Type
#End If
‘/////////////////////////////////
‘// End code GetOpenFileName //
‘/////////////////////////////////
Public Function GetMyFile(strTitle As String) As String
Dim OpenFile As OPENFILENAME
Dim lReturn As Long
OpenFile.lpstrFilter = “”
OpenFile.nFilterIndex = 1
OpenFile.hwndOwner = 0
OpenFile.lpstrFile = String(257, 0)
#If VBA7 Then
OpenFile.nMaxFile = LenB(OpenFile.lpstrFile) – 1
OpenFile.lStructSize = LenB(OpenFile)
#Else
OpenFile.nMaxFile = Len(OpenFile.lpstrFile) – 1
OpenFile.lStructSize = Len(OpenFile)
#End If
OpenFile.lpstrFileTitle = OpenFile.lpstrFile
OpenFile.nMaxFileTitle = OpenFile.nMaxFile
OpenFile.lpstrInitialDir = “C:\”
OpenFile.lpstrTitle = strTitle
OpenFile.flags = 0
lReturn = GetOpenFileName(OpenFile)
If lReturn = 0 Then
GetMyFile = “”
Else
GetMyFile = Trim(Left(OpenFile.lpstrFile, InStr(1, OpenFile.lpstrFile, vbNullChar) – 1))
End If
End Function
|
GetSystemMetrics |
Private Declare Function GetSystemMetrics Lib “USER32″ (ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetSystemMetrics Lib “USER32″ (ByVal nIndex As Long) As Long
|
GetTempPath |
Declare Function GetTempPath Lib “kernel32″ _
Alias “GetTempPathA” (ByVal nBufferLength As Long, _
ByVal lpbuffer As String) As LongDeclare PtrSafe Function GetTempPath Lib “kernel32″ _
Alias “GetTempPathA” (ByVal nBufferLength As longptr, _
ByVal lpbuffer As String) As Long
|
getTickCount |
Private Declare Function getTickCount Lib “kernel32″ Alias “QueryPerformanceCounter” (cyTickCount AsCurrency) As Long
Private Declare PtrSafe Function getTickCount Lib “kernel32″ Alias “QueryPerformanceCounter” (cyTickCountAs Currency) As Long
‘
|
getTime |
Private Declare Function timeGetTime Lib “winmm.dll” () As Long
Private Declare PtrSafe Function timeGetTime Lib “winmm.dll” () As Long
|
GetWindow |
Public Declare Function GetWindow Lib “USER32″ _
(ByVal hWnd As Long, ByVal wCmd As Long) As LongPublic Declare PtrSafe FunctionGetWindow Lib “USER32″ _
(ByVal hWnd As LongPtr, ByVal wCmd As Long) As LongPtr
|
GetWindowLong |
This is one of the few API functions that requires the Win64 compile constant:
#If VBA7 Then
#If Win64 Then
Private Declare PtrSafe Function GetWindowLongPtr Lib “USER32″ Alias “GetWindowLongPtrA” (ByValhWnd As LongPtr, ByVal nIndex As Long) As LongPtr
#Else
Private Declare PtrSafe Function GetWindowLongPtr Lib “USER32″ Alias “GetWindowLongA” (ByVal hWndAs LongPtr, ByVal nIndex As Long) As LongPtr
#End If
#Else
Private Declare Function GetWindowLongPtr Lib “USER32″ Alias “GetWindowLongA” (ByVal hWnd As Long,ByVal nIndex As Long) As Long
#End If
|
GetWindowsDirectory |
Declare Function GetWindowsDirectory& Lib “kernel32″ Alias _
“GetWindowsDirectoryA” (ByVal lpbuffer As String, _
ByVal nSize As Long)Declare PtrSafe Function GetWindowsDirectory& Lib “kernel32″ Alias _
“GetWindowsDirectoryA” (ByVal lpbuffer As String, _
ByVal nSize As LongPtr)
|
GetWindowText |
Public Declare Function GetWindowText Lib “USER32″ Alias “GetWindowTextA” _
(ByVal hWnd As Long, ByVal lpString As String, _
ByVal cch As Long) As LongPublic Declare PtrSafe Function GetWindowText Lib “USER32″ Alias “GetWindowTextA” _
(ByVal hWnd As LongPtr, ByVal lpString As String, _
ByVal cch As LongPtr) As Long
|
InternetGetConnectedState |
Public Declare Function InternetGetConnectedState _
Lib “wininet.dll” (lpdwFlags As Long, _
ByVal dwReserved As Long) As BooleanPublic Declare PtrSafe Function InternetGetConnectedState _
Lib “wininet.dll” (lpdwFlags As LongPtr, _
ByVal dwReserved As long) As Boolean
|
IsCharAlphaNumericA |
Private Declare Function IsCharAlphaNumericA Lib “USER32″ (ByVal byChar As Byte) As Long
Private Declare PtrSafe Function IsCharAlphaNumericA Lib “USER32″ (ByVal byChar As Byte) As Long
|
OleCreatePictureIndirect |
Private Declare Function OleCreatePictureIndirect Lib “oleaut32.dll” (PicDesc As PICTDESC, RefIID AsGUID, ByVal fPictureOwnsHandle As Long, IPic As IPicture) As LongPrivate Type PICTDESC
Size As Long
Type As Long
hPic As Long
hPal As Long
End Type
Private Declare PtrSafe Function OleCreatePictureIndirect Lib “oleaut32.dll” (PicDesc As PICTDESC, RefIIDAs GUID, ByVal fPictureOwnsHandle As LongPtr, IPic As IPicture) As LongPtrPrivate Type PICTDESC
Size As Long
Type As Long
hPic As LongPtr
hPal As LongPtr
End Type
|
OpenProcess |
#If VBA7 Then
Declare PtrSafe Function OpenProcess Lib “kernel32″ (ByVal _
dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal _
dwProcessId As Long) As LongPtr
#Else
Declare Function OpenProcess Lib “kernel32″ (ByVal _
dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal _
dwProcessId As Long) As Long
#End If
|
ReleaseDC |
Private Declare Function ReleaseDC Lib “USER32″ (ByVal hWnd As Long, ByVal hDC As Long) As Long
Private Declare PtrSafe Function ReleaseDC Lib “USER32″ (ByVal hWnd As LongPtr, ByVal hDC As LongPtr) As Long
|
SendMessage |
Public Declare Function SendMessageA Lib “user32″ (ByVal hWnd As Long, ByVal wMsg As Long, _
ByVal wParam As Long, lParam As Any) As Long
Public Declare PtrSafe Function SendMessageA Lib “user32″ (ByVal hWnd As LongPtr, ByVal wMsg As Long, _
ByVal wParam As LongPtr, lParam As Any) As LongPtr
|
SetActiveWindow |
Declare Function SetActiveWindow Lib “user32.dll” (ByVal hWnd As Long) As LongDeclare PtrSafe Function SetActiveWindow Lib “user32.dll” (ByVal hWnd As LongPtr) As LongPtr
|
SetCurrentDirectory |
Private Declare Function SetCurrentDirectoryA Lib “kernel32″ (ByVal lpPathName As String) As Long
Private Declare PtrSafe Function SetCurrentDirectoryA Lib “kernel32″ (ByVal lpPathName As String) As Long
|
SetWindowLongPtr |
This is one of the few API functions that requires the Win64 compile constant:
#If VBA7 Then
#If Win64 Then
Private Declare PtrSafe Function SetWindowLongPtr Lib “USER32″ Alias “SetWindowLongPtrA” (ByValhWnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
#Else
Private Declare Function SetWindowLongPtr Lib “USER32″ Alias “SetWindowLongA” (ByVal hWnd AsLongPtr, ByVal nIndex As Long, ByVal dwNewLong As LongPtr) As LongPtr
#End If
#Else
Private Declare Function SetWindowLongPtr Lib “USER32″ Alias “SetWindowLongA” (ByVal hWnd As Long,ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
#End If
|
SHBrowseForFolder |
#If VBA7 Then
Private 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 TypePrivate Declare PtrSafe Function SHBrowseForFolder Lib “shell32.dll” Alias “SHBrowseForFolderA” _
(lpBrowseInfo As BROWSEINFO) As LongPtr
#Else
Private 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 TypePrivate Declare Function SHBrowseForFolder Lib “shell32.dll” Alias “SHBrowseForFolderA” _
(lpBrowseInfo As BROWSEINFO) As Long
#End If
Private Const BIF_RETURNONLYFSDIRS = &H1
|
ShellExecute |
Private Declare 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 Long
Private 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
|
SHFileOperation |
#If VBA7 Then
Type SHFILEOPSTRUCT
hWnd As LongPtr
wFunc As Long
pFrom As String
pTo As String
fFlags As Integer
fAborted As Boolean
hNameMaps As Longptr
sProgress As String
End Type
Declare PtrSafe Function SHFileOperation Lib “shell32.dll” Alias “SHFileOperationA” _
(lpFileOp As SHFILEOPSTRUCT) As LongPtr
#Else
Type SHFILEOPSTRUCT
hWnd As Long
wFunc As Long
pFrom As String
pTo As String
fFlags As Integer
fAborted As Boolean
hNameMaps As Long
sProgress As String
End Type
Declare Function SHFileOperation Lib “shell32.dll” Alias “SHFileOperationA” _
(lpFileOp As SHFILEOPSTRUCT) As Long
#End If
|
SHGetPathFromIDList |
Private Declare Function SHGetPathFromIDList Lib “shell32.dll” Alias “SHGetPathFromIDListA” _
(ByVal pidl As Long, ByVal pszPath As String) As BooleanPrivate Declare PtrSafe Function SHGetPathFromIDList Lib “shell32.dll” Alias “SHGetPathFromIDListA” _
(ByVal pidl As LongPtr, ByVal pszPath As String) As Boolean
|
SHGetSpecialFolderLocation |
Private Declare Function SHGetSpecialFolderLocation Lib _
“shell32.dll” (ByVal hwndOwner As Long, ByVal nFolder As Long, _
pidl As ITEMIDLIST) As LongPrivate Declare PtrSafe Function SHGetSpecialFolderLocation Lib _
“shell32.dll” (ByVal hwndOwner As LongPtr, ByVal nFolder As Long, _
pidl As ITEMIDLIST) As LongPtr
Private Type SHITEMID
cb As Long
abID As Byte
End Type
Private Type ITEMIDLIST
mkid As SHITEMID
End Type
|
timeGetTime |
Private Declare Function timeGetTime Lib “winmm.dll” () As Long
Private Declare PtrSafe Function timeGetTime Lib “winmm.dll” () As Long
|