' ' [_WindowsAPI] ' Option Compare ' BINARY | TEXT | Database (if using MSAccess) Option Explicit #If VBA7 Then ' Use _WindowsAPI7 ' Read version info into buffer ' /* Length of buffer for info * ' /* Information from GetFileVersionSize * ' /* Filename of version stamped file * ' Declare PtrSafe 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 VerQueryValue Lib "version.dll" (pBlock As Any, ByVal lpSubBlock As String, ByVal lplpBuffer As LongPtr, puLen As Long) As Long #Else '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - Shell32.DLL '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function ExtractAssociatedIcon Lib "shell32.dll" Alias "ExtractAssociatedIconA" (ByVal hInst As Long, ByVal lpIconPath As String, lpiIcon As Long) As Long Public 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 Public Declare Function ShellExecuteForExplore Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, lpParameters As Any, lpDirectory As Any, ByVal nShowCmd As Long) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - Version.DLL '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' ' Returns size of version info in Bytes ' Public Declare Function GetFileVersionInfoSize Lib "Version.dll" Alias "GetFileVersionInfoSizeA" (ByVal lptstrFilename As String, lpdwHandle As Long) As Long ' ' Read version info into buffer: Arguments: ' 1. Length of buffer for info. ' 2.Information from GetFileVersionSize. ' 3. Filename of version stamped file ' Public 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 ' ' Returns selected version information from the specified 'version-information resource. ' Public Declare Function VerQueryValue Lib "Version.dll" Alias "VerQueryValueA" (pBlock As Any, ByVal lpSubBlock As String, lplpBuffer As Long, puLen As Long) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - Kernel 32 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, ByVal lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long Public Declare Function FileTimeToLocalFileTime Lib "kernel32" (lpFileTime As FILETIME, lpLocalFileTime As FILETIME) As Long Public Declare Function FileTimeToSystemTime Lib "kernel32" (lpFileTime As FILETIME, lpSystemTime As SystemTime) As Long Public Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As Long) As Long Public Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long Public Declare Function GetExitCodeProcess Lib "kernel32" (ByVal hProcess As Long, lpExitCode As Long) As Long Public Declare Function GetFileTime Lib "kernel32" (ByVal hFile As Long, lpCreationTime As FILETIME, lpLastAccessTime As FILETIME, lpLastWriteTime As FILETIME) As Long Public Declare Function GetFreeSpace Lib "kernel32" (ByVal wFlags As Integer) As Long Public Declare Function GetModuleFileName Lib "kernel32" Alias "GetModuleFileNameA" (ByVal hModule As Long, ByVal lpFileName As String, ByVal nSize As Long) As Long Public Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long Public Declare Function GetPrivateProfileInt Lib "kernel32" Alias "GetPrivateProfileIntA" (ByVal lpApplicationName As String, ByVal lpKeyName As String, ByVal nDefault As Long, ByVal lpFileName As String) As Long Public Declare Function GetPrivateProfileString Lib "kernel32" Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long Public Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, ByVal lpProcName As String) As Long Public Declare Function GetShortPathName Lib "kernel32" Alias "GetShortPathNameA" (ByVal lpszLongPath As String, ByVal lpszShortPath As String, ByVal cchBuffer As Long) As Long Public Declare Function GetSystemDirectory Lib "kernel32" Alias "GetSystemDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long Public Declare Function GetTempPath Lib "kernel32" Alias "GetTempPathA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long Public Declare Function GetVersion Lib "kernel32" () As Long Public Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long Public Declare Function GetWinFlags Lib "kernel32" Alias "GetWinFlagsA" () As Long Public Declare Function GetWindowsDirectory& Lib "kernel32" Alias "GetWindowsDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) Public Declare Function GlobalAlloc Lib "kernel32" (ByVal uFlags As Long, ByVal dwBytes As Long) As Long Public Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long Public Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long Public Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long Public Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long Public Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long Public Declare Function LocalFileTimeToFileTime Lib "kernel32" (lpLocalFileTime As FILETIME, lpFileTime As FILETIME) As Long Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long Public Declare Function SetFileTime Lib "kernel32" (ByVal hFile As Long, lpCreationTime As Any, lpLastAccessTime As Any, lpLastWriteTime As Any) As Long Public Declare Function SystemTimeToFileTime Lib "kernel32" (lpSystemTime As SystemTime, lpFileTime As FILETIME) As Long Public Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long Public Declare Function WritePrivateProfileString Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpString As Any, ByVal lpFileName As String) As Long Public Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long Public Declare Function lstrlenA Lib "kernel32" (ByVal lpString As Long) As Long Public Declare Function lstrlenW Lib "kernel32" (ByVal lpString As Long) As Long Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (ByRef Destination As Any, ByRef Source As Any, ByVal Length As Long) Public Declare Sub ExitProcess Lib "kernel32" (ByVal uExitCode As Long) Public Declare Sub GlobalMemoryStatus Lib "kernel32" (lpBuffer As MEMORYSTATUS) Public Declare Sub MoveMemory Lib "kernel32" Alias "RtlMoveMemory" (ByVal Destination As Long, ByRef Source As Byte, ByVal Length As Long) Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - User 32 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function BringWindowToTop Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function CloseClipboard Lib "user32" () As Long Public Declare Function EmptyClipboard Lib "user32" () As Long Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long Public Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long Public Declare Function FlashWindow Lib "user32" (ByVal hwnd As Long, ByVal bInvert As Long) As Long Public Declare Function GetActiveWindow Lib "user32" () 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 GetClientRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long Public Declare Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As Long Public Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function GetDesktopWindow Lib "user32" () As Long Public Declare Function GetParent Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long Public Declare Function GetWindow Lib "user32" (ByVal hwnd As Long, ByVal wCmd As Long) As Long Public Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long Public Declare Function GetWindowPlacement Lib "user32" (ByVal hwnd As Long, lpwndpl As WINDOWPLACEMENT) As Long Public Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long Public Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long Public Declare Function IsWindowVisible Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function IsZoomed Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function LockWindowUpdate Lib "user32.dll" (ByVal hwndLock As Long) As Long Public Declare Function MoveWindow Lib "user32" (ByVal hwnd As Long, ByVal x As Long, ByVal y As Long, ByVal dx As Long, ByVal dy As Long, ByVal fRepaint As Long) As Long Public Declare Function OpenClipboard Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As Long Public Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long Public Declare Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As Long) As Long Public Declare Function SetFocusAPI Lib "user32" Alias "SetForegroundWindow" (ByVal hwnd As Long) As Long Public 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 Public Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long Public Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) Public Declare Function WinHelp Lib "user32" Alias "WinHelpA" (ByVal hwnd As Long, ByVal lpHelpFile As String, ByVal wCommand As Long, ByVal dwData As Long) As Long Public Declare Function SetKeyboardState Lib "user32" (lppbKeyState As Any) As Long Public Declare Function GetKeyboardState Lib "user32" (pbKeyState As Any) As Long Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long Public Declare Function AttachThreadInput Lib "user32" (ByVal idAttach As Long, ByVal idAttachTo As Long, ByVal fAttach As Long) As Long Public Declare Function SetForegroundWindow Lib "user32" (ByVal hwnd As Long) As Long Public Declare Function SetFocusAPI Lib "user32" Alias "SetFocus" (ByVal hwnd As Long) As Long Public Const VK_SHIFT = &H10 Public Const VK_LSHIFT = &HA0 Public Const VK_RSHIFT = &HA1 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - AdvAPI 32 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - Toolhelp.dll '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function SystemHeapInfo Lib "ToolHelp.dll" (shi As SYSHEAPINFO) As Integer '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - Ole Accessibility / Automation / Programmability '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function AccessibleObjectFromWindow Lib "oleacc" (ByVal hwnd As Long, ByVal dwId As Long, ByRef riid As typUUID, ByRef ppvObject As Object) As Long ' Public Declare Function LoadTypeLibEx Lib "oleaut32.dll" (ByVal szFile As Long, ByVal regkind As Long, pptlib As ITypeLib) As Long Public Declare Function OleCreatePictureIndirect Lib "olepro32.dll" (lpPictDesc As PICTDESC, riid As GUID, ByVal fPictureOwnsHandle As Long, ipic As IPicture) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - msvbvm60 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function VarPtrArray Lib "msvbvm60.dll" Alias "VarPtr" (ptr() As Any) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - GDI 32 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function CreateBitmap Lib "gdi32" (ByVal nWidth As Long, ByVal nHeight As Long, ByVal nPlanes As Long, ByVal nBitCount As Long, lpBits As Any) As Long Public Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long Public Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long Public Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long Public Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long Public Declare Function GetDeviceCaps Lib "gdi32" (ByVal hdc As Long, ByVal nIndex As Long) As Long Public Declare Function PatBlt Lib "gdi32" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal dwRop As Long) As Long Public Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - GDI+ '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function GdipBitmapApplyEffect Lib "gdiplus.dll" (ByVal Image As Long, ByVal Effect As Long, ByVal roi As Long, ByVal useAuxData As Long, ByVal auxData As Long, ByVal auxDataSize As Long) As Long Public Declare Function GdipCreateBitmapFromFile Lib "gdiplus.dll" (ByVal Filename As Long, bitmap As Long) As Long Public Declare Function GdipCreateBitmapFromHBITMAP Lib "gdiplus.dll" (ByVal hbm As Long, ByVal hPal As Long, bitmap As Long) As Long Public Declare Function GdipCreateBitmapFromHICON Lib "gdiplus" (ByVal hIcon As Long, bitmap As Long) As Long Public Declare Function GdipCreateEffect Lib "gdiplus.dll" (ByVal cid1 As Long, ByVal cid2 As Long, ByVal cid3 As Long, ByVal cid4 As Long, Effect As Long) As Long Public Declare Function GdipCreateFromHDC Lib "gdiplus.dll" (ByVal hdc As Long, GpGraphics As Long) As Long Public Declare Function GdipCreateHBITMAPFromBitmap Lib "gdiplus.dll" (ByVal bitmap As Long, hbmReturn As Long, ByVal background As Long) As Long Public Declare Function GdipCreateHICONFromBitmap Lib "gdiplus" (ByVal bitmap As Long, hbmReturn As Long) As Long Public Declare Function GdipDeleteEffect Lib "gdiplus.dll" (ByVal Effect As Long) As Long Public Declare Function GdipDeleteGraphics Lib "gdiplus.dll" (ByVal graphics As Long) As Long Public Declare Function GdipDisposeImage Lib "gdiplus.dll" (ByVal Image As Long) As Long Public Declare Function GdipDrawImageRect Lib "gdiplus.dll" (ByVal graphics As Long, ByVal Image As Long, ByVal x As Single, ByVal y As Single, ByVal Width As Single, ByVal Height As Single) As Long Public Declare Function GdipGetImageHeight Lib "gdiplus.dll" (ByVal Image As Long, Height As Long) As Long Public Declare Function GdipGetImageThumbnail Lib "gdiplus.dll" (ByVal Image As Long, ByVal thumbWidth As Long, ByVal thumbHeight As Long, thumbImage As Long, Optional ByVal callback As Long = 0, Optional ByVal callbackData As Long = 0) As Long Public Declare Function GdipGetImageWidth Lib "gdiplus.dll" (ByVal Image As Long, Width As Long) As Long Public Declare Function GdipLoadImageFromStream Lib "gdiplus.dll" (ByVal stream As IUnknown, Image As Long) As Long Public Declare Function GdipSaveImageToFile Lib "gdiplus.dll" (ByVal Image As Long, ByVal Filename As Long, clsidEncoder As GUID, encoderParams As Any) As Long Public Declare Function GdipSaveImageToStream Lib "gdiplus.dll" (ByVal Image As Long, ByVal stream As IUnknown, clsidEncoder As GUID, encoderParams As Any) As Long Public Declare Function GdipSetEffectParameters Lib "gdiplus.dll" (ByVal Effect As Long, Params As Any, ByVal Size As Long) As Long Public Declare Function GdiplusShutdown Lib "gdiplus.dll" (ByVal token As Long) As Long Public Declare Function GdiplusStartup Lib "gdiplus.dll" (token As Long, inputbuf As GDIPStartupInput, Optional ByVal outputbuf As Long = 0) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - WinSock 32 '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Declare Function gethostbyaddr Lib "ws2_32.dll" (addr As Long, ByVal addrLen As Long, ByVal addrType As Long) As Long Public Declare Function gethostname Lib "ws2_32.dll" (ByVal szHost As String, ByVal dwHostLen As Long) As Long Public Declare Function inet_addr Lib "ws2_32.dll" (ByVal cp As String) As Long Public Declare Function InternetQueryOption Lib "wininet.dll" Alias "InternetQueryOptionA" (ByVal hInternet As Long, ByVal dwOption As Long, lpBuffer As INTERNET_CONNECTED_INFO, lpdwBufferLength As Long) As Boolean Public Declare Function InternetSetOption Lib "wininet.dll" Alias "InternetSetOptionA" (ByVal hInternet As Long, ByVal dwOption As Long, ByRef lpBuffer As Any, ByVal dwBufferLength As Long) As Long Public Declare Function gethostbyname Lib "ws2_32.dll" (ByVal szHost As String) As Long Public Declare Function WSACleanup Lib "ws2_32.dll" () As Long Public Declare Function WSAGetLastError Lib "ws2_32.dll" () As Long Public Declare Function WSAStartup Lib "ws2_32.dll" (ByVal wVersionRequired As Long, lpWSADATA As WSADATA) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - ICMP '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 'Close an Internet Control Message Protocol (ICMP) handle that IcmpCreateFile opens. 'http://msdn.microsoft.com/library/default.asp?url=/library/en-us/wcesdkr/htm/_wcesdk_icmpclosehandle.asp Public Declare Function IcmpCloseHandle Lib "ICMP" (ByVal IcmpHandle As Long) As Long 'Create a handle on which Internet Control Message Protocol (ICMP) requests can be issued. 'http://msdn.microsoft.com/library/default.asp?url=/library/en-us/wcesdkr/htm/_wcesdk_icmpcreatefile.asp Public Declare Function IcmpCreateFile Lib "ICMP" () As Long Public Declare Function IcmpSendEcho Lib "ICMP" (ByVal IcmpHandle As Long, ByVal DestinationAddress As Long, ByVal RequestData As String, ByVal RequestSize As Long, ByVal RequestOptions As Long, ReplyBuffer As ICMP_ECHO_REPLY, ByVal ReplySize As Long, ByVal TimeOut As Long) As Long '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Imports - OLE32.DLL '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Some useful functions for GUID work, borrowed from COM ' ' NOTE: StringFromGUID2 is identical in what it does to the other ole32.dll ' functions StringFromIID and StringFromCLSID. Therefore, they are not ' defined here Public Declare Function CLSIDFromProgID Lib "ole32.dll" (ByVal lpszProgID As Long, pclsid As GUID) As Long Public Declare Function CLSIDFromString Lib "ole32" (ByVal lpsz As Any, pclsid As GUID) As Long Public Declare Function CoCreateGuid Lib "ole32.dll" (rclsid As GUID) As Long Public Declare Function CoCreateInstance Lib "ole32.dll" (rclsid As GUID, pUnkOuter As Any, ByVal dwClsContext As Long, riid As GUID, ppvObj As IUnknown) As Long Public Declare Function CreateStreamOnHGlobal Lib "ole32" (ByVal hGlobal As Long, ByVal fDeleteOnRelease As Long, ByRef ppstm As Any) As Long Public Declare Function GetHGlobalFromStream Lib "ole32" (ByVal pstm As Any, ByRef phglobal As Long) As Long Public Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As typUUID) As Long Public Declare Function IsEqualGUID Lib "ole32.dll" (rguid1 As GUID, rguid2 As GUID) As Long Public Declare Function StringFromGUID2 Lib "ole32.dll" (rclsid As GUID, ByVal lpsz As Long, ByVal cbMax As Long) As Long 'Public Const IdleCountInterval = 1000 'Help Constants 'Public Const HELP_CONTEXT = &H1 'Display topic in ulTopic 'Public Const HELP_QUIT = &H2 'Terminate help 'Public Const HELP_INDEX = &H3 'Display index 'Public Const HELP_CONTENTS = &H3 'Public Const HELP_HELPONHELP = &H4 'Display help on using help 'Public Const HELP_SETINDEX = &H5 'Set the current Index for multi index help 'Public Const HELP_SETCONTENTS = &H5 'Public Const HELP_CONTXTPOPUP = &H8 'Public Const HELP_FORCEFILE = &H9 'Public Const HELP_KEY = &H101 'Display topic for keyword 'Public Const HELP_COMMAND = &H102 'Public Const HELP_PARTIALKEY = &H105 'call the search engine in winhelp '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Types / Structures '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' ' Only GDI+1.1: ' Public Type BlurParameters Radius As Single ExpandEdges As Long End Type Public Type FILETIME dwLowDate As Long dwHighDate As Long End Type Public Type GDIPStartupInput GdiplusVersion As Long DebugEventCallback As Long SuppressBackgroundThread As Long SuppressExternalCodecs As Long End Type Public Type HOSTENT hName As Long hAliases As Long hAddrType As Integer hLen As Integer hAddrList As Long End Type ' ' This structure describes the options that will be included in the ' header of an IP packet. ' ' http://msdn.microsoft.com/library/default.asp?url=/library/en-us/wcetcpip/htm/cerefIP_OPTION_INFORMATION.asp ' Public Type IP_OPTION_INFORMATION Ttl As Byte Tos As Byte Flags As Byte OptionsSize As Byte OptionsData As Long End Type ' ' This structure describes the data that is returned in response to an echo request. ' http://msdn.microsoft.com/library/default.asp?url=/library/en-us/wcesdkr/htm/_wcesdk_icmp_echo_reply.asp ' Public Type ICMP_ECHO_REPLY Address As Long Status As Long RoundTripTime As Long DataSize As Long Reserved As Integer ptrData As Long Options As IP_OPTION_INFORMATION Data As String * 250 End Type Public Type ICMP_OPTIONS Ttl As Byte Tos As Byte Flags As Byte OptionsSize As Byte OptionsData As Long End Type Public Type INTERNET_CONNECTED_INFO dwConnectedState As Long dwFlags As Long End Type Public Type MEMORYSTATUS dwLength As Long dwMemoryLoad As Long dwTotalPhys As Long dwAvailPhys As Long dwTotalPageFile As Long dwAvailPageFile As Long dwTotalVirtual As Long dwAvailVirtual As Long End Type Type POINTAPI x As Long y As Long End Type Type POINTL x As Long y As Long End Type Type RECT Left As Long Top As Long Right As Long Bottom As Long End Type Type WINDOWPLACEMENT Length As Long Flags As Long showCmd As Long ptMinPosition As POINTAPI ptMaxPosition As POINTAPI rcNormalPosition As RECT End Type Public Type SYSHEAPINFO dwSize As Long wUserFreePercent As Integer wGDIFreePercent As Integer hUserSegment As Integer hGDISegment As Integer End Type Public Type OSVERSIONINFO dwOSVersionInfoSize As Long dwMajorVersion As Long dwMinorVersion As Long dwBuildNumber As Long dwPlatformId As Long szCSDVersion As String * 128 ' Maintenance string for PSS usage End Type Public Type OSVERSIONINFOEX dwOSVersionInfoSize As Long dwMajorVersion As Long dwMinorVersion As Long dwBuildNumber As Long dwPlatformId As Long szCSDVersion As String * 128 ' Maintenance string for PSS usage wServicePackMajor As Integer wServicePackMinor As Integer wSuiteMask As Integer wProductType As Byte wReserved As Byte End Type Public Type PICTDESC cbSizeOfStruct As Long PicType As Long hImage As Long xExt As Long yExt As Long End Type 'Only GDI+1.1: Public Type SharpenParameters Radius As Single Amount As Single End Type Public Type TSize x As Double y As Double End Type Type SECURITY_ATTRIBUTES nLength As Long lpSecurityDescriptor As LongPtr bInheritHandle As Long End Type ' ' Structure contains version information about a file. ' (This information is language and code page independent.) Public Type VS_FIXEDFILEINFO dwSignature As Long 'Contains the value 0xFEEFO4BD (szKey) dwStrucVersion As Long 'Specifies the binary version number of this structure. dwFileVersionMS As Long 'most significant 32 bits of the file's binary version number. dwFileVersionLS As Long 'least significant 32 bits of the file's binary version number. dwProductVersionLS As Long 'most sig. 32 bits of binary version of product this file was distributed with. dwFileFlagsMask As Long 'least sig. 32 bits of binary version of product this file was distributed with. dwProductVersionMS As Long 'Contains a bitmask that specifies the valid bits in dwFileFlags. dwFileFlags As Long 'Contains a bitmask that specifies the Boolean attributes of the file. dwFileOS As Long 'operating system for which this file was designed. dwFileType As Long 'general type of file. dwFileSubtype As Long 'function of the file. dwFileDateMS As Long 'most sig. 32 bits of the file's 64-bit binary creation date and time stamp. dwFileDateLS As Long 'least sig. 32 bits of the file's 64-bit binary creation date and time stamp. End Type Public Type typUUID 'GUID Data1 As Long Data2 As Integer Data3 As Integer Data4(7) As Byte End Type ' Note that although Variants now have ' a VT_GUID type, this type is unsupported in VBA, ' so we must define our own here that will have the same ' binary layout as all GUIDs are expected by COM to ' have. ' Public Type GUID Data1 As Long Data2 As Integer Data3 As Integer Data4(7) As Byte ' 0 to 7 (8 Bytes) End Type Public Type EncoderParameter UUID As GUID NumberOfValues As Long Type As Long Value As Long End Type Public Type EncoderParameters Count As Long Parameter As EncoderParameter End Type Public Type WSADATA wVersion As Integer wHighVersion As Integer szDescription(0 To MAX_WSADescription) As Byte szSystemStatus(0 To MAX_WSASYSStatus) As Byte wMaxSockets As Integer wMaxUDPDG As Integer dwVendorInfo As Long End Type Public Type SystemTime wYear As Integer wMonth As Integer wDayOfWeek As Integer wDay As Integer wHour As Integer wMinute As Integer wSecond As Integer wMilliseconds As Integer End Type '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ' Enumerations '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Public Enum EShellShowConstants essSW_Hide = 0 essSW_MAXIMIZE = 3 essSW_MINIMIZE = 6 essSW_SHOWMAXIMIZED = 3 essSW_SHOWMINIMIZED = 2 essSW_SHOWNORMAL = 1 essSW_SHOWNOACTIVATE = 4 essSW_SHOWNA = 8 essSW_SHOWMINNOACTIVE = 7 essSW_SHOWDEFAULT = 10 essSW_RESTORE = 9 essSW_SHOW = 5 End Enum Public Enum ShellAndWaitResult Success = 0 Failure = 1 TimeOut = 2 InvalidParameter = 3 SysWaitAbandoned = 4 UserWaitAbandoned = 5 UserBreak = 6 End Enum Public Enum ActionOnBreak IgnoreBreak = 0 AbandonWait = 1 PromptUser = 2 End Enum Public Enum PicFileType pictypeBMP = 1 pictypeGIF = 2 pictypePNG = 3 pictypeJPG = 4 End Enum ' ' RGB Color Constants RGB(R,G,B) = Long(&HBBGGRR) ' Public Enum eColorPalette Aqua = &HFFFF00 Black = &H0 Blue = &HFF0000 Gray = &HC0C0C0 Green = &HFF00 Manila = &HA0FFFF PaleAqua = &HFFFFA0 Red = &HFF White = &HFFFFFF Yellow = &HC0C0 End Enum ' ' API declarations. '******************************************************************* 'End user functions '******************************************************************* #End If