Using API Functions
The potential uses for API functions are endless. You can use API functions to modify the System menu, obtain system information, or even switch between running applications. In fact, you can accomplish so many things using API function that entire books are devoted to the topic. The remainder of this chapter covers several of the common uses of API functions.
Manipulating the Windows Registry
Four built-in VBA functions help you manipulate the Windows registry. They include GetAllSettings, GetSetting, SaveSetting, and DeleteSetting. These four functions only allow you to manipulate and work with a specific branch of the registry, HKEY_CURRENT_USER\Software\VB, and VBA program Settings. There are times when it is necessary to read from or write to other parts of the registry. This is one situation in which the Windows API can really help you out. Using the Windows RegQueryValueEx function, you can extract information from registry keys. Using the RegSetValueEx function, you can write information to the registry. The declarations for these two functions (found in the basAPICalls module) look like this:'The RegQueryValueExA function is used to
'read information from the Windows registry
Declare Function RegQueryValueEx _
Lib "advapi32.dll" Alias "RegQueryValueExA" _
(ByVal hKey As Long, ByVal lpValueName As String, _
ByVal lpReserved As Long, lpType As Long, _
lpData As Any, lpcbData As Long) As Long
'The RegSetValueExA function is used to
'write information to the Windows registry
Declare Function RegSetValueEx _
Lib "advapi32.dll" Alias "RegSetValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal Reserved As Long, _
ByVal dwType As Long, _
lpData As Any, _
ByVal cbData As Long) As Long
Before you use either function, you must first obtain a handle to the registry key you wish to affect. This requires the RegOpenKeyEx function:'The RegOpenKeyExA function is used to
'Return a numeric value that references
'a specific registry key
Declare Function RegOpenKeyEx _
Lib "advapi32.dll" Alias "RegOpenKeyExA" _
(ByVal hKey As Long, ByVal lpSubKey As String, _
ByVal ulOptions As Long, ByVal samDesired As Long, _
phkResult As Long) As Long
Finally, when you are done reading from or saving to the registry, you must use the RegCloseKey function to close the registry key. The declaration for the RegCloseKey function looks like this:'The RegCloseKey fucntion closes the designated
'registry key
Public Declare Function RegCloseKey _
Lib "advapi32.dll" (ByVal hKey As Long) As Long
Listing 23.2 shows how you can use the RegQueryValueEx function to read from the registry.
Listing 23.2 Using RegQueryValueEx to Read Registry Information
Private Sub cmdRead_Click()
Dim strValue As String * 256
Dim lngRetval As Long
Dim lngLength As Long
Dim lngKey As Long
'Retrieve handle of the registry key
If RegOpenKeyEx(HKEY_CURRENT_USER, _
Me.txtKeyName.Value, _
0, KEY_QUERY_VALUE, lngKey) Then
End If
lngLength = 256
'Retrieve the value of the key
lngRetval = RegQueryValueEx( _
lngKey, Me.txtValueName, 0, 0, ByVal strValue, lngLength)
Me.txtValue = Left(strValue, lngLength)
'Close the key
RegCloseKey (lngKey)
End Sub
You will find this code in the frmRegistry form in the sample database. Notice that the code first retrieves a handle to the requested registry key. It then uses the RegQueryValueEx function to retrieve the designated value from the registry. After the code is complete, it closes the registry key. For example, you could request the value Last User from the Software\Microsoft\Office\11.0\Access\Settings registry key. The value stored for the Last User setting displays in the txtValue text box.Listing 23.3 shows how you can use the RegSetValueEx function to write to the registry.
Listing 23.3 Using RegSetValueEx to Write Information to the Registry
Private Sub cmdWrite_Click()
Dim strValue As String
Dim strKeyName As String
Dim lngRetval As Long
Dim lngLength As Long
Dim lngKey As Long
'Create string with Key name
strKeyName = Me.txtKeyName.Value & vbNullString
'Retrieve handle of the registry key
If RegOpenKeyEx(HKEY_CURRENT_USER, _
strKeyName, _
0, KEY_WRITE, lngKey) Then
End If
'Create string with string to store
strValue = Me.txtValue.Value & vbNullString
'Create variable with length of string to store
lngLength = Len(Me.txtValue) + 1
'Save the value to the key
lngRetval = RegSetValueEx( _
lngKey, Me.txtValueName, 0, REG_SZ, _
ByVal strValue, lngLength)
'Close the key
RegCloseKey (lngKey)
End Sub
The routine first opens a handle to the designated registry key. It then calls the RegSetValueEx function, passing the handle, the value you wish to modify, the type of data the key contains, and the new value. Finally, it closes the registry key.CAUTIONI generally do not make a practice of writing information to the Windows registry. If you write to an important registry key and make a mistake, you can render the Windows operating environment unusable. When you must write to the Windows registry, do so sparingly, and carefully.NOTEListing 23.3 shows you how to write to a registry key that contains a string. To write to a registry that expects a DWORD value, you must use the REG_DWORD constant rather than the REG_SZ constant.
Getting Information About the Operating Environment
By using Windows API calls, you can get volumes of information about the system environment, including the type of hardware on which the application is running, the amount of memory that exists or is available, and the operating system version under which the application is running. It is handy and professional to include system information in your application's Help About box. It also is important to include this system information in your error handling and logging, because such information can help you diagnose the problem. This is discussed in Chapter 16, "Error Handling: Preparing for the Inevitable."Figure 23.1 shows a Custom About dialog box that includes system environment information. This form uses several Windows API calls to get the system information displayed on the form.
Figure 23.1. A Custom About dialog box illustrating the capability to obtain system information from the Windows API.

Before you can call any of the DLL functions required to obtain this information, you must declare all the necessary functions to the compiler. This example accomplishes this in the General Declarations section of the module basUtils. You must also include any constants and type structures used by the DLL calls in the General Declarations section. Listing 23.4 shows what the General Declarations section of basAPICalls looks like.
Listing 23.4 The General Declarations Section of basAPICalls
[View full width]Option Compare Database
Option Explicit
Public Const MAX_PATH = 160
'The GetVersionEx function gets information about '
'the version of the operating system that is currently '
'running. The information is filled into the type
'structure OSVERSIONINFO.
Declare Function abGetVersionEx _
Lib "kernel32" _
Alias "GetVersionExA" _
(lpOSInfo As OSVERSIONINFO) As Boolean
Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
strReserved As String * 128
End Type
'The GetSystemMetrics function utilizes three constants to
'determine whether a mouse is present, and to determine
'the width and height of the screen.
Const SM_CXSCREEN = 0
Const SM_CYSCREEN = 1
Const SM_MOUSEPRESENT = 19
Declare Function abGetSystemMetrics _
Lib "user32" _
Alias "GetSystemMetrics" _
(ByVal nIndex As Long) As Long
'The GlobalMemoryStatus function retrieves information
'about current available memory. It points to a type
'structure called SYSTEM_INFO, filling in its elements
'with relevant memory information.
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
Declare Sub abGlobalMemoryStatus _
Lib "kernel32" _
Alias "GlobalMemoryStatus" _
(lpBuffer As MEMORYSTATUS)
'The GetSystemInfo function returns information about
'the system. It fills in the type structure SYSTEM_INFO
'with relevant information about the system.
Type SYSTEM_INFO
dwOemID As Long
dwPageSize As Long
lpMinimumApplicationAddress As Long
lpMaximumApplicationAddress As Long
dwActiveProcessorMask As Long
dwNumberOrfProcessors As Long
dwProcessorType As Long
dwAllocationGranularity As Long
dwReserved As Long
End Type
Declare Sub abGetSystemInfo Lib "kernel32" _
Alias "GetSystemInfo" _
(lpSystemInfo As SYSTEM_INFO)
'The GetWindowsDirectory function retrieves the name of the
'directory within which Windows is running
Declare Function abGetWindowsDirectory _
Lib "kernel32" _
Alias "GetWindowsDirectoryA" _
(ByVal lpBuffer As String, _
ByVal nSize As Long) As Long
'The GetSystemDirectory function retrieves the name of the
'directory in which the Windows system files reside.
Declare Function abGetSystemDirectory _
Lib "kernel32" _
Alias "GetSystemDirectoryA" _
(ByVal lpBuffer As String, _
ByVal nSize As Long) As Long
'The GetTempPath function retrieves the name of the
'directory where temporary files are stored.
Declare Function abGetTempPath _
Lib "kernel32" _
Alias "GetTempPathA" _
(ByVal nBufferLength As Long, _
ByVal lpBuffer As String) As Long
'The GetCommandLine function retrieves the command
'line for the current process.
Declare Function abGetCommandLine _
Lib "kernel32" _
Alias "GetCommandLineA" () _
As String
'The GetClassName Function returns the class name
'of a window
Declare Function abGetClassName _
Lib "user32" _
Alias "GetClassNameA" _
(ByVal hwnd As Long, _
ByVal lpClassName As String, _
ByVal nMaxCount As Long) _
As Long
'Gets the handle of a parent window
Declare Function abGetParent _
Lib "user32" _
Alias "GetParent" _
(ByVal hwnd As Long) _
As Long
'The GetWindowText Function gets the title of the
'current window
Declare Function abGetWindowText _
Lib "user32" _
Alias "GetWindowTextA" _
(ByVal hwnd As Long, _
ByVal lpString As String, _
ByVal cch As Long) _
As Long
'The SetWindowText Function modifies the title of the
'current window
Declare Function abSetWindowText _
Lib "user32" _
Alias "SetWindowTextA" _
(ByVal hwnd As Long, _
ByVal lpString As String) _
As Long
'The GetDriveType Function returns an integer
'indicating the drive type
Public Const DRIVE_UNKNOWN = 0
Public Const DRIVE_UNAVAILABLE = 1
Public Const DRIVE_REMOVABLE = 2
Public Const DRIVE_FIXED = 3
Public Const DRIVE_REMOTE = 4
Public Const DRIVE_CDROM = 5
Public Const DRIVE_RAMDISK = 6
Declare Function abGetDriveType _
Lib "kernel32" _
Alias "GetDriveTypeA" _
(ByVal nDrive As String) _
As Long
'The GetDiskFreeSpace Function determines the amount of
'free space on the active drive
Declare Function abGetDiskFreeSpace _
Lib "kernel32" _
Alias "GetDiskFreeSpaceA" _
(ByVal lpRootPathName As String, _
lpSectorsPerCluster As Long, _
lpBytesPerSector As Long, _
lpNumberOfFreeClusters As Long, _
lpTotalNumberOfClusters As Long) _
As Long
'Constants used by RegOpenKeyEx
Public Const KEY_QUERY_VALUE = &H1
Public Const KEY_SET_VALUE = &H2
Public Const READ_CONTROL = &H20000
Public Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)
Public Const SYNCHRONIZE = &H100000
Public Const KEY_CREATE_SUB_KEY = &H4
Public Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY)

Public Const HKEY_CLASSES_ROOT = &H80000000
Public Const HKEY_CURRENT_CONFIG = &H80000005
Public Const HKEY_CURRENT_USER = &H80000001
Public Const HKEY_DYN_DATA = &H80000006
Public Const HKEY_LOCAL_MACHINE = &H80000002
Public Const HKEY_PERFORMANCE_DATA = &H80000004
Public Const HKEY_USERS = &H80000003
Public Const REG_SZ = 1 ' Unicode nul terminated string
Public Const REG_DWORD = 4 ' 32-bit number
'The RegOpenKeyExA function is used to
'Return a numeric value that references
'a specific registry key
Declare Function RegOpenKeyEx _
Lib "advapi32.dll" Alias "RegOpenKeyExA" _
(ByVal hKey As Long, ByVal lpSubKey As String, _
ByVal ulOptions As Long, ByVal samDesired As Long, _
phkResult As Long) As Long
'The RegQueryValueExA function is used to
'read information from the Windows registry
Declare Function RegQueryValueEx _
Lib "advapi32.dll" Alias "RegQueryValueExA" _
(ByVal hKey As Long, ByVal lpValueName As String, _
ByVal lpReserved As Long, lpType As Long, _
lpData As Any, lpcbData As Long) As Long
'The RegSetValueExA function is used to
'write information to the Windows registry
Declare Function RegSetValueEx _
Lib "advapi32.dll" Alias "RegSetValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal Reserved As Long, _
ByVal dwType As Long, _
lpData As Any, _
ByVal cbData As Long) As Long
'The RegCloseKey fucntion closes the designated
'registry key
Public Declare Function RegCloseKey _
Lib "advapi32.dll" (ByVal hKey As Long) As Long
As you can see, several type structures, constants, and Declare statements are required to obtain all the information that appears on the form. When the form (frmSystemInformation) is opened, all the Windows API functions are called, and the text boxes on the form are filled with the system information. The Open event of the form frmSystemInformation calls a subroutine called GetSysInfo, which is shown in Listing 23.5.
Listing 23.5 The GetSysInfo Subroutine
Sub GetSysInfo(frmAny As Form)
Dim intMousePresent As Integer
Dim strBuffer As String
Dim intLen As Integer
Dim MS As MEMORYSTATUS
Dim SI As SYSTEM_INFO
Dim strCommandLine As String
frmAny.txtScreenResolution = abGetSystemMetrics(SM_CXSCREEN) & _
" By " & abGetSystemMetrics(SM_CYSCREEN)
intMousePresent = CBool(abGetSystemMetrics(SM_MOUSEPRESENT))
frmAny.txtMousePresent = IIf(intMousePresent, "Mouse Present", _
"No Mouse Present")
'Set the length member before you call GlobalMemoryStatus
MS.dwLength = Len(MS)
abGlobalMemoryStatus MS
frmAny.txtMemoryLoad = MS.dwMemoryLoad & "%"
frmAny.txtTotalPhysical = Format(Fix(MS.dwTotalPhys / 1024), _
"###,###") & "K"
frmAny.txtAvailablePhysical = Format(Fix(MS.dwAvailPhys / 1024), _
"###,###") & "K"
frmAny.txtTotalVirtual = Format(Fix(MS.dwTotalVirtual / 1024), _
"###,###") & "K"
frmAny.txtAvailableVirtual = Format(Fix(MS.dwAvailVirtual / 1024), _
"###,###") & "K"
abGetSystemInfo SI
frmAny.txtProcessorMask = SI.dwActiveProcessorMask
frmAny.txtNumberOfProcessors = SI.dwNumberOfProcessors
frmAny.txtProcessorType = SI.dwProcessorType
strBuffer = Space(MAX_PATH)
intLen = abGetWindowsDirectory(strBuffer, MAX_PATH)
frmAny.txtWindowsDir = Left(strBuffer, intLen)
strBuffer = Space(MAX_PATH)
intLen = abGetSystemDirectory(strBuffer, MAX_PATH)
frmAny.txtSystemDir = Left(strBuffer, intLen)
strBuffer = Space(MAX_PATH)
intLen = abGetTempPath(MAX_PATH, strBuffer)
frmAny.txtTempDir = Left(strBuffer, intLen)
End Sub
Now take a look at this subroutine in detail. The subroutine calls the function GetSystemMetrics (aliased as abGetSystemMetrics) three times. The first time, it is sent the constant SM_CXSCREEN, and the second time, it is sent the constant SM_CYSCREEN. These calls return the horizontal and vertical screen resolutions. When passed the constant SM_MOUSEPRESENT, the GetSystemMetrics function returns a logical True or False, indicating whether a mouse is present.The GlobalMemoryStatus API call fills in a structure with several pieces of information regarding memory. The code fills the elements of the structure with the memory load, total and available physical memory, and total and available virtual memory.The GetSystemInfo API call also provides you with valuable system information. It fills in a structure with several technical tidbits, including the active processor mask, the number of processors, and the processor type.Finally, the function calls GetWindowsDirectory, GetSystemDirectory, and GetTempPath. These three functions return the Windows folder, System folder, and temp file path, respectively. Notice that buffer space is pre-allocated before each call. Because each call returns the length of the folder name retrieved, you then take the characters on the left side of the buffer for the number of characters specified in the return value.
Determining Drive Types and Available Drive Space
Often, it is necessary to determine the types of drives available and the amount of space free on each drive. Fortunately, Windows API functions are available to help you to accomplish these tasks. The frmListDrives form lists the type of each drive installed on the system and the amount of free space on each drive, as shown in Figure 23.2. The declarations that are required for the APIs are shown in Listing 23.6.
Listing 23.6 API Declarations
'The GetDriveType Function returns an integer
'indicating the drive type
Public Const DRIVE_UNKNOWN = 0
Public Const DRIVE_UNAVAILABLE = 1
Public Const DRIVE_REMOVABLE = 2
Public Const DRIVE_FIXED = 3
Public Const DRIVE_REMOTE = 4
Public Const DRIVE_CDROM = 5
Public Const DRIVE_RAMDISK = 6
Declare Function abGetDriveType _
Lib "kernel32" _
Alias "GetDriveTypeA" _
(ByVal nDrive As String) _
As Long
'The GetDiskFreeSpace function determines the amount of
'free space on the active drive
Declare Function abGetDiskFreeSpace _
Lib "kernel32" _
Alias "GetDiskFreeSpaceA" _
(ByVal lpRootPathName As String, _
lpSectorsPerCluster As Long, _
lpBytesPerSector As Long, _
lpNumberOfFreeClusters As Long, _
lpTotalNumberOfClusters As Long) _
As Long
Figure 23.2. The frmListDrives form showing the type of each drive installed on the system and the amount of free space on each drive.

The Click event of the cmdListDrives command button located on frmListDrives calls a subroutine called GetDriveInfo, sending it the txtDrives text box. Listing 23.7 shows the GetDriveInfo procedure.
Listing 23.7 The GetDriveInfo Procedure
Sub GetDriveInfo(ctlAny As Control)
Dim intDrive As Integer
Dim strDriveLetter As String
Dim strDriveType As String
Dim strSpaceFree As String
'Loop through all drives
For intDrive = 65 To 90 'A through Z
strDriveLetter = (Chr(intDrive) & ":\")
'Get Drive Type
strDriveType = TypeOfDrive(strDriveLetter)
'Get Space Free
strSpaceFree = NumberOfBytesFree(strDriveLetter)
ctlAny.Value = _
ctlAny.Value & _
Left(strDriveLetter, 2) & _
" - " & strDriveType & _
IIf(strDriveType <> "Drive Doesn't Exist", _
strSpaceFree, ") & _
vbCrLf
Next intDrive
End Sub
The routine loops through all available drive letters. For each drive letter, the code calls two user-defined functions: TypeOfDrive and NumberOfBytesFree. Listing 23.8 shows the TypeOfDrive function.
Listing 23.8 The TypeOfDrive Function
Function TypeOfDrive(ByVal strDrive As String) As String
Dim intDriveType As Integer
Dim strDriveType As String
intDriveType = abGetDriveType(strDrive)
Select Case intDriveType
Case DRIVE_UNKNOWN
strDriveType = "Type Unknown"
Case DRIVE_UNAVAILABLE
strDriveType = "Drive Doesn't Exist"
Case DRIVE_REMOVABLE
strDriveType = "Removable Drive"
Case DRIVE_FIXED
strDriveType = "Fixed Drive"
Case DRIVE_REMOTE
strDriveType = "Network Drive"
Case DRIVE_CDROM
strDriveType = "CD-ROM"
Case DRIVE_RAMDISK
strDriveType = "RAM Disk"
End Select
TypeOfDrive = strDriveType
End Function
The TypeOfDrive function receives a drive letter as a parameter. It calls the Windows API function GetDriveType to determine the type of drive whose drive letter was passed to the function. The GetDriveType function returns a numeric value that indicates the type of the specified drive. The returned value is evaluated with a case statement, and text representing the drive type is returned from the function.The NumberOfBytesFree function determines how many bytes are free on a particular drive, as shown in Listing 23.9.
Listing 23.9 The NumberOfBytesFree Function
Function NumberOfBytesFree(ByVal strDrive As String) As String
Dim lngSectors As Long
Dim lngBytes As Long
Dim lngFreeClusters As Long
Dim lngTotalClusters As Long
Dim intErrNum As Integer
intErrNum = abGetDiskFreeSpace(strDrive, lngSectors, _
lngBytes, lngFreeClusters, lngTotalClusters)
NumberOfBytesFree = " with " & _
Format((CDbl(lngBytes) * CDbl(lngSectors)) * _
CDbl(lngFreeClusters), "#,##0") & _
" Bytes Free"
End Function
This function receives a drive letter as a parameter. It then calls the GetDiskFreeSpace Windows API function, sending it the drive letter and several long integers. These long integers are filled in with the information required to determine the number of bytes free on the specified drive.After the code determines the type of drive and number of bytes free, the GetDriveInfo procedure concatenates the information with the text contained in a text box on the frmListDrives form. If the drive specified is unavailable, the amount of available disk space is not printed.