Sample .BAS set of functions:
Attribute VB_Name = "INIReg"
Option Explicit
' 18 apr 1997 By Nicolas Schneider
' 05 mar 1998 By Nicolas Schneider
'--- Define severity codes
Public Const ERROR_SUCCESS As Long = 0&
Public Const ERROR_ACCESS_DENIED As Long = 5
Public Const ERROR_MORE_DATA As Long = 234
Public Const ERROR_NO_MORE_ITEMS As Long = 259
'--- Registry Constants
Public Const HKEY_CLASSES_ROOT As Long = &H80000000
Public Const HKEY_CURRENT_USER As Long = &H80000001
Public Const HKEY_LOCAL_MACHINE As Long = &H80000002
Public Const HKEY_USERS As Long = &H80000003
Public Const HKEY_PERFORMANCE_DATA As Long = &H80000004
Public Const HKEY_CURRENT_CONFIG As Long = &H80000005
Public Const HKEY_DYN_DATA As Long = &H80000006
'--- masks for the predefined standard access types
Private Const STANDARD_RIGHTS_ALL As Long = &H1F0000
Private Const SPECIFIC_RIGHTS_ALL As Long = &HFFFF
Private Const READ_CONTROL As Long = &H20000
Private Const STANDARD_RIGHTS_READ = (READ_CONTROL)
Private Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000
Private Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)
Private Const SYNCHRONIZE As Long = &H100000
Private Const KEY_CREATE_LINK As Long = &H20
Private Const KEY_CREATE_SUB_KEY As Long = &H4
Private Const KEY_ENUMERATE_SUB_KEYS As Long = &H8
Private Const KEY_EVENT As Long = &H1
Private Const KEY_NOTIFY As Long = &H10
Private Const KEY_QUERY_VALUE As Long = &H1
Private Const KEY_SET_VALUE As Long = &H2
Private Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or
KEY_CREATE_SUB_KEY) And (Not SYNCHRONIZE))
Private Const KEY_ALL_ACCESS = ((STANDARD_RIGHTS_ALL Or KEY_QUERY_VALUE Or
KEY_SET_VALUE Or KEY_CREATE_SUB_KEY Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY
Or KEY_CREATE_LINK) And (Not SYNCHRONIZE))
Private Const KEY_READ = ((STANDARD_RIGHTS_READ Or KEY_QUERY_VALUE Or
KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY) And (Not SYNCHRONIZE))
Private Const KEY_EXECUTE = (KEY_READ)
'--- Open/Create Options
Private Const REG_OPTION_NON_VOLATILE As Long = 0&
Private Const REG_OPTION_VOLATILE As Long = &H1
'--- Key creation/open disposition
Private Const REG_CREATED_NEW_KEY As Long = &H1
Private Const REG_OPENED_EXISTING_KEY As Long = &H2
'--- Predefined Value Types
Private Const REG_NONE As Long = 0 'No value type
Private Const REG_SZ As Long = 1 'Unicode nul
terminated string
Private Const REG_EXPAND_SZ As Long = 2 'Unicode nul
terminated string w/enviornment var
Private Const REG_BINARY As Long = 3 'Free form binary
Private Const REG_DWORD As Long = 4 '32-bit number
Private Const REG_DWORD_LITTLE_ENDIAN As Long = 4 '32-bit number
(same as REG_DWORD)
Private Const REG_DWORD_BIG_ENDIAN As Long = 5 '32-bit number
Private Const REG_LINK As Long = 6 'Symbolic Link
(unicode)
Private Const REG_MULTI_SZ As Long = 7 'Multiple Unicode
strings
Private Const REG_RESOURCE_LIST As Long = 8 'Resource list in
the resource map
Private Const REG_FULL_RESOURCE_DESCRIPTOR As Long = 9 'Resource list in
the hardware description
Private Const REG_RESOURCE_REQUIREMENTS_LIST As Long = 10
Private Type FILETIME
dwLowDateTime As Long
dwHighDateTime As Long
End Type
Private Declare Function RegCloseKey Lib "advapi32" (ByVal hKey As Long) As
Long
Private Declare Function RegCreateKeyEx Lib "advapi32.dll" Alias
"RegCreateKeyExA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal
Reserved As Long, ByVal lpClass As String, ByVal dwOptions As Long, ByVal
samDesired As Long, ByVal lpSecurityAttributes As Long, lhkResult As Long,
lpdwDisposition As Long) As Long
Private Declare Function RegOpenKeyEx Lib "advapi32" Alias "RegOpenKeyExA"
(ByVal hKey As Long, ByVal lpSubKey As String, ByVal dwReserved As Long,
ByVal samDesired As Long, lhkResult As Long) As Long
Private Declare Function RegQueryValueEx Lib "advapi32" Alias
"RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As String, ByVal
lpdwReserved As Long, lpdwType As Long, lpData As Any, lpcbData As Long) As
Long
Private Declare Function RegEnumKeyEx Lib "advapi32.dll" Alias
"RegEnumKeyExA" (ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpName As
String, lpcbName As Long, ByVal lpReserved As Long, lpClass As Any,
lpcbClass As Long, lpftLastWriteTime As FILETIME) As Long
Private Declare Function RegEnumValue Lib "advapi32.dll" Alias
"RegEnumValueA" (ByVal hKey As Long, ByVal dwIndex As Long, ByVal
lpValueName As String, lpcbValueName As Long, ByVal lpReserved As Long,
lpType As Long, ByVal lpData As String, lpcbData As Long) As Long
' Note that if you declare the lpData parameter as String, you must pass it
By Value.
Private 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
Private Declare Function RegDeleteKey Lib "advapi32.dll" Alias
"RegDeleteKeyA" (ByVal hKey As Long, ByVal lpSubKey As String) As Long
Private Declare Function RegDeleteValue Lib "advapi32.dll" Alias
"RegDeleteValueA" (ByVal hKey As Long, ByVal lpValueName As String) As Long
'--- INI Declarations
Private Declare Function GetPrivateProfileString Lib "kernel32" Alias
"GetPrivateProfileStringA" (ByVal lpApplicationName As Any, ByVal lpKeyName
As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal
nSize As Long, ByVal lpFilename As String) As Long
Private 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
Private Declare Function WriteProfileString Lib "kernel32" Alias
"WriteProfileStringA" (ByVal lpszSection As String, ByVal lpszKeyName As
String, ByVal lpszString As String) As Long
Private mbaHex() As Byte
Public Function fgyINIRegSetValue(alhKey As Long, asSubKey As String,
asSetValue As String, Optional avValue As Variant) As Boolean
'--- Note: This function will create the key or value if it doesn't exist.
Dim lhkResult As Long
Dim lResult As Long
Dim lCreate As Long
On Error GoTo ERROR_HANDLER
'--- Open or Create the key
lResult = RegCreateKeyEx(alhKey, asSubKey, 0&, vbNullString,
REG_OPTION_NON_VOLATILE, KEY_SET_VALUE, 0, lhkResult, lCreate)
' If asSetValue = "" And VarType(avValue) = vbEmpty And UCase$(asSubKey) =
"SOFTWARE\WINUP\INSTAPPL\" Then
' '--- Delete the Key if
' lResult = RegDeleteKey(alhKey, asSubKey)
' Else
Select Case VarType(avValue)
Case vbEmpty: lResult = RegDeleteValue(lhkResult, asSetValue)
Case vbNull: lResult = RegDeleteValue(lhkResult, asSetValue)
Case vbInteger: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_DWORD, CLng(avValue), 4)
Case vbLong: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_DWORD, CLng(avValue), 4)
Case vbSingle: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_BINARY, CLng(avValue), 4)
Case vbDouble: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_BINARY, CDbl(avValue), 8)
Case vbCurrency: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_BINARY, CCur(avValue), 8)
Case vbDate: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_BINARY, CCur(avValue), 8)
Case vbString: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_SZ, ByVal CStr(avValue), Len(avValue))
Case vbObject
Case vbError: lResult = RegDeleteValue(lhkResult, asSetValue) '---
No parameters
Case vbBoolean: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_DWORD, CBool(avValue), 4)
Case vbVariant: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_DWORD, avValue, 16)
Case vbDataObject
Case vbByte: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_DWORD, CByte(avValue), 1)
Case vbArray
Case Else
End Select
'--- Close the key
RegCloseKey lhkResult
' End If
'--- Return SetRegValue Result
fgyINIRegSetValue = (lResult = ERROR_SUCCESS)
Exit Function
ERROR_HANDLER:
MsgBox "ERROR #" & CStr(Err.Number) & " : " & Err.Description & vbLf &
"Please exit and try again.", vbExclamation
fgyINIRegSetValue = False
Resume Next
End Function
Public Function fgyINIRegSetValueBYTE(alhKey As Long, asSubKey As String,
asSetValue As String, abaValue() As Byte, alByteCnt As Long, Optional alType
As Long) As Boolean
'--- Note: This function will create the key or value if it doesn't exist.
Dim lhkResult As Long
Dim lResult As Long
Dim lCreate As Long
On Error GoTo ERROR_HANDLER
'--- Open or Create the key
lResult = RegCreateKeyEx(alhKey, asSubKey, 0&, vbNullString,
REG_OPTION_NON_VOLATILE, KEY_SET_VALUE, 0, lhkResult, lCreate)
Select Case alType
Case REG_EXPAND_SZ: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_EXPAND_SZ, abaValue(0), alByteCnt)
Case REG_MULTI_SZ: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_MULTI_SZ, abaValue(0), alByteCnt)
Case Else: lResult = RegSetValueEx(lhkResult, asSetValue, 0&,
REG_BINARY, abaValue(0), alByteCnt)
End Select
'--- Close the key
RegCloseKey lhkResult
'--- Return SetRegValue Result
fgyINIRegSetValueBYTE = (lResult = ERROR_SUCCESS)
On Error GoTo 0
Exit Function
ERROR_HANDLER:
MsgBox "ERROR #" & CStr(Err.Number) & " : " & Err.Description & vbLf &
"Please exit and try again.", vbExclamation
fgyINIRegSetValueBYTE = False
Resume Next
End Function
Public Function fgsINIRegGetString(alInKey As Long, ByVal asSubKey As
String, ByVal asValName As Variant)
Dim lhSubKey As Long
Dim ldwType As Long
Dim lBufferLen As Long
Dim lRet As Long
Dim sBuffer As String
Dim sRetVal As String
lRet = RegOpenKeyEx(alInKey,
...
read more »