Microsoft KB Archive/210115

From BetaArchive Wiki
Knowledge Base


ACC2000: How to Convert API Calls from 16-bit to 32-bit

Article ID: 210115

Article Last Modified on 10/11/2006



APPLIES TO

  • Microsoft Access 2000 Standard Edition



This article was previously published under Q210115


Advanced: Requires expert coding, interoperability, and multiuser skills.

This article applies to a Microsoft Access database (.mdb) and to a Microsoft Access project (.adp).


SUMMARY

Because the architecture of Windows 95 and later and Windows NT is 32-bit, there are several differences in the application programming interface (API) from the 16-bit API of Windows 3.x. This article shows you how to convert code that contains 16-bit API calls to 32-bit API calls so that the code will run successfully in a 32-bit operating environment. This article discusses the following topics:

  • Why 16-bit API calls do not work in a 32-bit operating environment
  • Tips on how to make the conversion process easier
  • List of converted declaration statements for common API functions that you can copy into your modules


MORE INFORMATION

Why 16-bit API Calls Do Not Work in a 32-bit Operating Environment

You cannot use a 16-bit API call in the Windows 95 and later or Windows NT 32-bit operating environment for the following reasons:

  • The API library names (dll) are different, for example:
    16-bit 32-bit
    User.dll User32.dll
    Kernel.dll Kernel32.dll
    GDI.dll GDI32.dll
  • Parameter data types are often different, for example:
    16-bit 32-bit
    Integer Long
    Integer Byte
    Double Long
    NOTE: This is not a complete list. You should watch closely for different parameter data types when you convert code that makes an API call or supplies parameters to an API call.
  • API function names are case-sensitive. This differs from the 16-bit API, which is not case-sensitive. For example, in a 16-bit API call, the following statements are equivalent:

    Declare Function GetVersion Lib "KERNEL" () as Long
    Declare Function gEtVeRsIoN Lib "KERNEL" () as Long
  • However, when converted to a 32-bit API, the following statements are not equivalent because the function names are case-sensitive:

    Declare Function GetVersion Lib "KERNEL32" () as Long
    Declare Function gEtVeRsIoN Lib "KERNEL32" () as Long
  • Some API functions have different versions to accommodate ANSI and UniCode strings. If an API listed in this article is limited to use under a specific operating system in 32-bit, it will be noted with the API function.

Tips on How to Make the Conversion Process Easier

You can reduce the work involved with converting your existing code by adopting these practices:

  • When you declare an API procedure, use an alias for the procedure name. The alias must be unique from the function name. If it is not, the alias will be deleted automatically.
  • When you declare the data type returned by the function or the data type of parameters passed to the function, use an As clause rather than the type declaration characters (%, $, and so on).

List of Converted Declaration Statements for Common API Functions

Following is a listing of 16-bit and 32-bit Declare statements for common API calls that you can use as reference when you convert your code to 32-bit.

BitBlt

16-bit:

Declare Function BitBlt Lib "GDI" (ByVal hDestDC As Integer, _
   ByVal X As Integer, ByVal Y As Integer, ByVal nWidth As _
   Integer,  ByVal nHeight As Integer, ByVal hSrcDC As Integer, _
   ByVal XSrc As Integer, ByVal YSrc As Integer, ByVal dwRop As _
   Long) As Long

32-bit:

Declare Function apiBitBlt Lib "gdi32" Alias "BitBlt" (ByVal _
   hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth _
   As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal _
   XSrc  As Long, ByVal YSrc As Long, ByVal dwRop As Long) As Long

CheckMenuItem

16-bit:

Declare Function CheckMenuItem Lib "User" (ByVal hMenu As _
   Integer, ByVal wIDCheckItem As Integer, ByVal wCheck As _
   Integer) As Integer

32-bit:

Declare Function apiCheckMenuItem Lib "user32" Alias _
   "CheckMenuItem" (ByVal hMenu As Long, ByVal wIDCheckItem _
   As Long, ByVal wCheck As Long) As Long

ChooseColor

16-bit:

Declare Function ChooseColor_API Lib "COMMDLG.DLL" Alias _
   "ChooseColor" (pCHOOSECOLOR As ChooseColor) As Integer

32-bit:

Type CHOOSECOLOR
   lStructSize As Long
   hwndOwner As Long
   hInstance  As Long
   RgbResult As Long
   lpCustColors As Long
   Flags As Long
   lCustData As Long
   lpfnHook As Long
   lpTemplateName As Long
End Type
Declare Function apiChooseColor Lib "comdlg32.dll" Alias _
   "ChooseColorA" (pChoosecolor As CHOOSECOLOR) As Long

NOTE: You can use the ChooseColor functionality of this API by using the Common Dialog ActiveX control included with the Microsoft Office Developer.


CloseClipboard

16-bit:

Declare Function CloseClipboard Lib "User" () As Integer

32-bit:

Declare Function apiCloseClipboard Lib "user32" Alias _
   "CloseClipboard" () As Long

CommDlgExtendedError

16-bit:

Declare Function CommDlgExtendedError Lib "COMMDLG.DLL" () _
   As Long

32-bit:

Declare Function apiCommDlgExtendedError Lib "comdlg32.dll" _
   Alias "CommDlgExtendedError" () As Long

CopyMemory

16-bit:

Declare Sub hmemcpy Lib "kernel" (hpvDest As Any, hpvSrc As _
   Any, ByVal cbBytes As Long)

32-bit:

Global Const GMEM_MOVEABLE = &H2
Global Const GMEM_ZEROINIT = &H40
Global Const GHND = (GMEM_MOVEABLE Or GMEM_ZEROINIT)
Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _
   (hpvDest As Any, hpvSource As Any, ByVal cbCopy As Long)

CreateCompatibleBitmap

16-bit:

Declare Function CreateCompatibleBitmap Lib "GDI" (ByVal _
   hDC As Integer, ByVal nWidth As Integer, ByVal nHeight As _
   Integer) As Integer

32-bit:

Declare Function apiCreateCompatibleBitmap Lib "gdi32" Alias _
   "CreateCompatibleBitmap" (ByVal hdc As Long, ByVal nWidth As _
   Long, ByVal nHeight As Long) As Long

CreateCompatibleDC

16-bit:

Declare Function CreateCompatibleDC Lib "GDI" (ByVal hdc As _
   Integer) As Integer

32-bit:

Declare Function apiCreateCompatibleDC Lib "Gdi32" (ByVal hdc _
   As Long) As Long

DeleteDC

16-bit:

Declare Function DeleteDC Lib "GDI" (ByVal hDC As Integer) _
   As Integer

32-bit:

Declare Function apiDeleteDC Lib "gdi32" Alias "DeleteDC" _
   (ByVal hdc As Long) As Long

DrawMenuBar

16-bit:

Declare Sub DrawMenuBar Lib "User" (ByVal hWnd As Integer)

32-bit:

Declare Function apiDrawMenuBar Lib "user32" Alias _
   "DrawMenuBar" (ByVal hwnd As Long) As Long

EmptyClipboard

16-bit:

Declare Function EmptyClipboard Lib "User" () As Integer

32-bit:

Declare Function apiEmptyClipboard Lib "user32" Alias _
   "EmptyClipboard" () As Long

EnableMenuItem

16-bit:

Declare Function EnableMenuItem Lib "User" (ByVal hMenu As _
   Integer, ByVal wIDEnableItem As Integer, ByVal wEnable _
   As Integer) As Integer

32-bit:

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

ExitWindows

16-bit:

Declare Function ExitWindows Lib "User" (ByVal dwReturnCode _
   As Long, ByVal wReserved As Integer) As Integer

32-bit:

Declare Function apiExitWindows Lib "user32" Alias _
   "ExitWindows" (ByVal dwReserved As Long, ByVal uReturnCode _
   As Long) As Long

FindExecutable

16-bit:

Declare Function FindExecutable Lib "Shell" (ByVal _
   lpszFile As String, ByVal lpszDir As String, ByVal _
   lpszResult As String) As Integer

32-bit:

Declare Function apiFindExecutable Lib "shell32.dll" Alias _
   "FindExecutableA" (ByVal lpFile As String, ByVal lpDirectory _
   As String, ByVal lpResult As String) As Long

FindWindow

16-bit:

Declare Function FindWindow Lib "user"(ByVal lpclassname As _
   Any, ByVal lpCaption As Any) As Integer

32-bit:

Declare Function apiFindWindow Lib "User32" Alias "FindWindowA" _
   (ByVal lpclassname As Any, ByVal lpCaption As Any) as Long

fRead

16-bit:

Declare Function fRead Lib "kernel" Alias "lread" (ByVal _
   hFile As Integer, ByVal lpBuff As Long, ByVal nBuff _
   As Integer) As Long

32-bit:

Use the FileCopy Statement within Microsoft Access 7.0 and 97, or
   see the CopyFile API call above.

Fwrite

16-bit:

Declare Function fWrite Lib "kernel" Alias "_lwrite" (ByVal _
   hFile As Integer, ByVal lpBuff As Long, ByVal nBuff As Integer) _
   As Long

32-bit:

Use the FileCopy Statement, or see the CopyFile API call above.

GetActiveWindow

16-bit:

Declare Function GetActiveWindow Lib "User" () As Integer

32-bit:

Declare Function apiGetActiveWindow Lib "user32" Alias _
   "GetActiveWindow" () As Long

GetClassName

16-bit:

Declare Function GetClassName Lib "User" (ByVal hWnd _
   As Integer, ByVal lpClassName As String, ByVal nMaxCount _
   As Integer) As Integer

32-bit:

Declare Function apiGetClassName Lib "user32" Alias _
   "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName _
   As String, ByVal nMaxCount As Long) As Long

GetClipboardData

16-bit:

Declare Function GetClipboardData Lib "User" (ByVal _
   wFormat As Integer) As Integer

32-bit:

Declare Function apiGetClipboardData Lib "user32" Alias _
   "GetClipboardDataA" (ByVal wFormat As Long) As Long

GetCursorPos

16-bit:

Declare Sub GetCursorPos Lib "User" (lpPoint As POINTAPI)
32-bit: Type POINTAPI
   x as Long
   y as Long
End Type
Declare Sub apiGetCursorPos Lib "User32" (lpPoint _
   As POINTAPI)

GetDC

16-bit:

Declare Function GetDC Lib "User" (ByVal hWnd As Integer) _
   As Integer

32-bit:

Declare Function apiGetDC Lib "user32" Alias "GetDC" (ByVal _
   hwnd As Long) As Long

GetDesktopWindow

16-bit:

Declare Function GetDesktopWindow Lib "User" () As Integer

32-bit:

Declare Function apiGetDesktopWindow Lib "user32" Alias _
   "GetDesktopWindow" () As Long

NOTE: You can also use GetWindow to perform the same function.


GetDeviceCaps

16-bit:

Declare Function GetDeviceCaps Lib "GDI" (ByVal hDC _
   As Integer, ByVal nIndex As Integer) As Integer

32-bit:

Declare Function apiGetDeviceCaps Lib "gdi32" Alias _
   "GetDeviceCaps" (ByVal hdc As Long, ByVal nIndex As Long) _
   As Long

GetDriveType

16-bit:

Declare Function GetDriveType Lib "Kernel" (ByVal nDrive _
   As Integer) As Integer

32-bit:

Declare Function apiGetDriveType Lib "kernel32" Alias _
   "GetDriveTypeA" (ByVal nDrive As String) As Long

GetFileVersionInfo

16-bit:

Declare Function GetFileVersionInfo Lib "VER.DLL" _
  (ByVal lpszFileName As String, ByVal lpdwHandle As Long, _
  ByVal cbbuf As Long, ByVal lpvdata As String) As Integer

32-bit:

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

GetFileVersionInfoSize

16-bit:

Declare Function GetFileVersionInfoSize Lib "VER.DLL" _
  (ByVal lpszFileName As String, lpdwHandle As Long) As Long

32-bit:

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

GetKeyState

16-bit:

Declare Function GetKeyState Lib "User" (ByVal nVirtKey _
   As Integer) As Integer

32-bit:

Declare Function apiGetKeyState Lib "user32" Alias _
   "GetKeyState" (ByVal nVirtKey As Long) As Integer

GetMenu

16-bit:

Declare Function GetMenu Lib "User" (ByVal hWnd As _
   Integer) As Integer

32-bit:

Declare Function apiGetMenu Lib "user32" Alias "GetMenu" _
   (ByVal hwnd As Long) As Long

GetMenuState

16-bit:

Declare Function GetMenuState Lib "User" (ByVal hMenu _
   As Integer, ByVal wId As Integer, ByVal wFlags As _
   Integer) As Integer

32-bit:

Declare Function apiGetMenuState Lib "user32" Alias _
   "GetMenuState" (ByVal hMenu As Long, ByVal wID As Long, _
   ByVal wFlags As Long) As Long

GetModuleFileName

16-bit:

Declare Function GetModuleFileName Lib "Kernel" (ByVal _
   hModule As Integer, ByVal lpFilename As String, ByVal _
   nSize As Integer) As Integer

32-bit:

Declare Function apiGetModuleFileName Lib "kernel32" Alias _
   "GetModuleFileNameA" (ByVal hModule As Long, ByVal _
   lpFileName As String, ByVal nSize As Long) As Long

GetModuleHandle

16-bit: Declare Function GetModuleHandle Lib "Kernel" (ByVal _
   lpModuleName As String) As Integer

32-bit:

Declare Function apiGetModuleHandle Lib "kernel32" Alias _
   "GetModuleHandleA" (ByVal lpModuleName As String) As Long

GetModuleUsage

16-bit:

Declare Function GetModuleUsage Lib "Kernel" (ByVal _
   hModule As Integer) As Integer

32-bit:

This function has been deleted. Each Win32 application
   runs in its own address space.

GetOpenFileName

16-bit:

Declare Function GetOpenFileName Lib "COMMDLG.DLL" _
  (OPENFILENAME As tagOPENFILENAME) As Integer

32-bit:

Type tagOPENFILENAME
   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

Declare Function apiGetOpenFileName Lib "comdlg32.dll" _
   Alias "GetOpenFileNameA" (OPENFILENAME as tagOPENFILENAME) _
   As Long

GetParent

16-bit:

Declare Function GetParent Lib "User" (ByVal hWnd As _
   Integer) As Integer

32-bit:

Declare Function apiGetParent Lib "user32" Alias _
   "GetParent" (ByVal hwnd As Long) As Long

GetPrivateProfileString

16-bit:

Declare Function GetPrivateProfileString Lib "Kernel" _
   (ByVal lpApplicationName As String, ByVal lpKeyName As _
   Any, ByVal lpDefault As String, ByVal lpReturnedString As _
   String, ByVal nSize As Integer, ByVal lpFileName As String) _
   As Integer

32-bit:

Declare Function apiGetPrivateProfileString 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

GetSaveFileName

16-bit:

Declare Function GetSaveFileName Lib "COMMDLG.DLL" _
   (OPENFILENAME As tagOPENFILENAME) As Integer

32-bit:

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 Long
   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

Declare Function apiGetSaveFileName Lib "comdlg32.dll" _
   Alias "GetSaveFileNameA" (pOpenfilename as OPENFILENAME) As Long

NOTE: You can achieve the same functionality with the Common Dialog OLE control included with the Microsoft Office Developer.


GetSubMenu

16-bit:

Declare Function GetSubMenu Lib "User" (ByVal hMenu _
   As Integer, ByVal nPos As Integer) As Integer

32-bit:

Declare Function apiGetSubMenu Lib "user32" Alias _
   "GetSubMenu" (ByVal hMenu As Long, ByVal nPos As Long) _
   As Long

GetSystemDirectory

16-bit:

Declare Function GetSystemDirectory Lib "Kernel" _
   (ByVal lpBuffer As String, ByVal nSize As Integer) As _
   Integer

32-bit:

Declare Function apiGetSystemDirectory Lib "kernel32" _
   Alias "GetSystemDirectoryA" (ByVal lpBuffer As String, _
   ByVal nSize As Long) As Long

GetSystemMenu

16-bit:

Declare Function GetSystemMenu Lib "user" (ByVal _
   hWnd As Integer, ByVal flag As Integer) As Integer

32-bit:

Declare Function apiGetSystemMenu Lib "user32" Alias _
   "GetSystemMenu" (ByVal hWnd As Long, ByVal flag As Long) _
   As Long

GetSystemMetrics

16-bit:

Declare Function GetSystemMetrics Lib "User" (ByVal _
   nIndex As Integer) As Integer

32-bit:

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

GetVersion

16-bit:

Declare Function GetVersion Lib "Kernel" () As Long

32-bit:

Declare Function apiGetVersion Lib "kernel32" Alias _
   "GetVersion" () As Long

GetWindow

16-bit:

Declare Function GetWindow Lib "User" (ByVal hWnd As _
   Integer, ByVal wCmd As Integer) As Integer

32-bit:

Declare Function apiGetWindow Lib "user32" Alias _
   "GetWindow" (ByVal hwnd As Long, ByVal wCmd As Long) _
   As Long

GetWindowLong

16-bit:

Declare Function GetWindowLong Lib "User" (ByVal hWnd _
   As Integer, ByVal nIndex As Integer) As Long

32-bit:

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

GetWindowRect

16-bit:

Declare Sub GetWindowRect Lib "GDI" (ByVal hWnd As _
   Integer, lpRect As RECT)

32-bit:

Type RECT_Type
   left As Long
   top As Long
   right As Long
   bottom As Long
End Type

Declare Function apiGetWindowRect Lib "user32" Alias _
   "GetWindowRect" (ByVal hwnd As Long, lpRect As RECT_Type) _
   As Long

GetWindowText

16-bit:

Declare Function GetWindowText Lib "User" (ByVal hWnd As _
   Integer, ByVal lpString As String, ByVal aint As Integer) As _
   Integer

32-bit:

Declare Function apiGetWindowText Lib "user32" Alias _
   "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString _
   As String, ByVal cch As Long) As Long

GetWindowWord

16-bit:

Declare Function GetWindowWord Lib "User" (ByVal _
   hWnd As Integer, ByVal nIndex As Integer) As Integer

32-bit:

Declare Function apiGetWindowWord Lib "user32" Alias _
   "GetWindowWord" (ByVal hwnd As Long, ByVal nIndex As _
   Long) As Integer

GetWindowsDirectory

16-bit:

Declare Function GetWindowsDirectory Lib "Kernel" _
  (ByVal lpbuffer As String, ByVal nsize As Integer) As Integer

32-bit:

Declare Function apiGetWindowsDirectory Lib _
   "Kernel32" Alias "GetWindowsDirectoryA" (ByVal _
   lpbuffer As String, ByVal nsize As Long) As Long

GlobalAlloc

16-bit:

Declare Function GlobalAlloc Lib "Kernel" (ByVal _
   wFlags As Integer, ByVal dwBytes As Long) As Integer

32-bit:

Declare Function apiGlobalAlloc Lib "kernel32" Alias _
   "GlobalAlloc" (ByVal wFlags As Long, ByVal dwBytes _
   As Long) As Long

GlobalFree

16-bit:

Declare Function GlobalFree Lib "Kernel" (ByVal hMem _
   As Integer) As Integer

32-bit:

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

GlobalLock

16-bit:

Declare Function GlobalLock Lib "Kernel" (ByVal hMem _
   As Integer) As Long

32-bit:

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

GlobalSize

16-bit:

Declare Function GlobalSize Lib "Kernel" (ByVal hMem _
   As Integer) As Long

32-bit:

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

GlobalUnlock

16-bit:

Declare Function GlobalUnlock Lib "Kernel" (ByVal _
   hMem As Integer) As Integer

32-bit:

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

hmemcpy

16-bit:

Declare Sub hmemcpy Lib "kernel" (hpvDest As Any, _
   hpvSrc As Any, ByVal cbBytes As Long)

32-bit:

This subfunction is not available in 32-bit environments.

The function, CopyMemory, is the replacement for hmemcpy.


IsIconic

16-bit:

Declare Function IsIconic Lib "User" (ByVal hWnd As _
   Integer) As Integer

32-bit:

Declare Function apiIsIconic Lib "user32" Alias _
   "IsIconic" (ByVal hwnd As Long) As Long

IsWindowVisible

16-bit:

Declare Function IsWindowVisible Lib "User" (ByVal _
   hWnd As Integer) As Integer

32-bit:

Declare Function apiIsWindowVisible Lib "user32" Alias _
   "IsWindowVisible" (ByVal hwnd As Long) As Long

IsZoomed

16-bit:

Declare Function IsZoomed Lib "User" (ByVal hWnd As _
   Integer) As Integer

32-bit:

Declare Function apiIsZoomed Lib "user32" Alias _
   "IsZoomed" (ByVal hwnd As Long) As Long

lstrcpy

16-bit:

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

32-bit:

Declare Function apilstrcpy Lib "kernel32" Alias "lstrcpyA" _
   (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long

NetWkstaGetInfo

16-bit:

Declare Function NetWkstaGetInfo Lib "NetAPI.DLL" _
   (ByVal lServer As Long, ByVal sLevel As Integer, _
   ByVal pbBuffer As Long, ByVal cbBuffer As Integer, _
   pcbTotalAvail As Integer) As Integer

32-bit:

Declare Function apiNetWkstaGetInfo Lib "NetAPI32.dll"_
   Alias NetWkstaGetInfo (ByVal lServer as Integer, ByVal _
   sLevel as Integer, ByVal pbBuffer as Long, cbBuffer as _
   Integer, pcbTotalAvail as Integer) As Integer

NOTE: This function is available only in the Windows NT environment. You can use the CurrentUser() function to obtain the currently logged on user.


OpenClipboard

16-bit:

Declare Function OpenClipboard Lib "User" (ByVal _
   hWnd As Integer) As Integer

32-bit:

Declare Function apiOpenClipboard Lib "user32" Alias _
   "OpenClipboard" (ByVal hwnd As Long) As Long

Playsound

16-bit:

Declare Function sndplaysound Lib "mmsystem" (ByVal _
   filename as String, ByVal snd_async as Integer) As Integer

32-bit:

Declare Function apisndPlaySound Lib "winmm" Alias _
"sndPlaySoundA" (ByVal filename As String, ByVal snd_async _
As Long) As Long

ReleaseDC

16-bit:

Declare Function ReleaseDC Lib "User" (ByVal hWnd _
   As Integer, ByVal hDC As Integer) As Integer

32-bit:

Declare Function apiReleaseDC Lib "user32" Alias _
   "ReleaseDC" (ByVal hwnd As Long, ByVal hdc As Long) _
   As Long

SelectObject

16-bit:

Declare Function SelectObject Lib "GDI" (ByVal hDC _
   As Integer, ByVal hObject As Integer) As Integer

32-bit:

Declare Function apiSelectObject Lib "GDI32" Alias _
   "SelectObject" (ByVal hdc As Long, ByVal hObject As _
   Long) As Long

SetActiveWindow

16-bit:

Declare Function SetActiveWindow Lib "User" (ByVal _
   hWnd As Integer) As Integer

32-bit:

Declare Function apiSetActiveWindow Lib "user32" _
   Alias "SetActiveWindow" (ByVal hwnd As Long) As Long

SetClipBoardData

16-bit:

Declare Function SetClipboardData Lib "User" _
   (ByVal wFormat As Integer, ByVal hMem As Integer) As Integer

32-bit:

Declare Function apiSetClipboardData Lib "User32.dll" _
   Alias "SetClipboardData" (ByVal wFormat as Long, _
   ByVal hMem as Long) as Long

SetKeyboardState

16-bit:

Declare Sub SetKeyboardState Lib "User" (lpKeyState As Any)

32-bit:

Declare Function apiSetKeyboardState Lib "user32" Alias_
   "SetKeyboardState" (lppbKeyState As Byte) As Long

SetSysModalWindow

16-bit:

Declare Function SetSysModalWindow Lib "User" _
   (ByVal hwnd As Integer) As Integer

32-bit:

This function has been deleted.

SetWindowLong

16-bit:

Declare Function SetWindowLong Lib "User" (ByVal hWnd _
   As Integer, ByVal nIndex As Integer, ByVal dwNewLong _
   As Long) As Long

32-bit:

Declare Function apiSetWindowLong Lib "user32" Alias _
   "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex _
   As Long, lNewLong as Long) As Long

SetWindowPos

16-bit:

Declare Sub SetWindowPos Lib "User" (ByVal hWnd As Integer,_
   ByVal hWndInsertAfter As Integer, ByVal X As Integer, _
   ByVal Y As Integer, ByVal cx As Integer, ByVal cy _
   As Integer, ByVal wFlags As Integer)

32-bit:

Declare Function apiSetWindowPos Lib "user32" Alias _
   "SetWindowPos" (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

ShellExecute

16-bit:

Declare Function ShellExecute Lib "SHELL" (ByVal _
   hwnd As Integer, ByVal lpszOp As String, ByVal lpszFile _
   As String, ByVal lpszParams As String, ByVal lpszDir As _
   String, ByVal fsShowCmd As Integer) As Integer

32-bit:

Declare Function apiShellExecute 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

ShowWindow

16-bit:

Declare Function ShowWindow Lib "User" (ByVal hWnd _
   As Integer, ByVal nCmdShow As Integer) As Integer

32-bit:

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

WNetAddConnection

16-bit:

Declare Function WNetAddConnection Lib "User" (ByVal _
   lpszNetPath As String, ByVal lpszPassword As String, _
   ByVal lpszLocalName As String) As Integer

32-bit:

Declare Function apiWNetAddConnection Lib "mpr.dll" Alias _
   "WNetAddConnectionA" (ByVal lpszNetPath As String, ByVal _
   lpszPassword As String, ByVal lpszLocalName As String) As Long

WNetCancelConnection

16-bit:

Declare Function WNetCancelConnection Lib "User" (ByVal _
   lpszName As String, ByVal bForce As Integer) As Integer

32-bit:

Declare Function apiWNetCancelConnection Lib "mpr.dll" _
   Alias "WNetCancelConnectionA" (ByVal lpszName As _
   String, ByVal fForce As Long) As Long

WNetGetUser

16-bit: Declare Function WNetGetUser Lib "USER.EXE" (ByVal _ szUser As String, lpnBufferSize As Integer) As Integer 32-bit:

Declare Function apiWNetGetUser Lib "mpr.dll" Alias _
   "WNetGetUserA" (ByVal lpName As String, ByVal _
   lpUserName As String, lpnLength As Long) As _
   Long
Declare Function WNetGetUser Lib "mpr" Alias _
   "WNetGetUserA" (ByVal lpName As String, ByVal _
   lpUserName As String, lpnLength As Long) As Long

WritePrivateProfileString

16-bit:

Declare Function WritePrivateProfileString Lib _
   "Kernel" (ByVal lpApplicationName As String, ByVal _
   lpKeyName As Any, ByVal lpString As Any, ByVal _
   lplFileName As String) As Integer

32-bit:

Declare Function apiWritePrivateProfileString Lib _
   "kernel32" Alias "WritePrivateProfileStringA" _
   (ByVal lpApplicationName As String, ByVal lpKeyName _
   As Any, ByVal lpString As Any, ByVal lpFileName As _
   String) As Long

REFERENCES

For more information about converting code that calls dynamic link libraries, in the Visual Basic Editor, click Microsoft Visual Basic Help on the Help menu, type convert code that calls a DLL in the Office Assistant or the Answer Wizard, and then click Search to view the topic.

  • Dan Appleman's Visual Basic Programmer's Guide to the Win32 API by Dan Appleman.

Published by SAMS. ISBN: 0672315904.

  • Microsoft Win32 Programmer's Reference Volumes 1 - 5 published by Microsoft Press.


Keywords: kbfaq kbhowto kbprogramming KB210115