Link to home
Start Free TrialLog in
Avatar of groone
groone

asked on

Registry

I asked this before and I guess I sort of jumped the gun with the answer.

I am having a problem writing to the registry of an NT system.  I can write to the registry using savesetting and retrieve using getsetting, but I need to be able to choose the HKEY root I want

I've used  The following api's and no luck. They allow me to write in a win95/98 registry no problem.  I dont even get an error in winNT.
'-------------------
Declare Function RegSetValueExString Lib "advapi32.dll" Alias "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, ByVal reserved As Long, ByVal dwType As Long, ByVal lpValue As String, ByVal cbData As Long) As Long
Declare Function RegSetValueExLong Lib "advapi32.dll" Alias "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, ByVal reserved As Long, ByVal dwType As Long, lpValue As Long, ByVal cbData As Long) As Long

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, lpSecurityAttributes As Long, phkResult As Long, lpdwDisposition As Long) As Long
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 Byte, ByVal cbData As Long) As Long
Declare Function RegCloseKey Lib "advapi32.dll" (ByVal hKey As Long) As Long
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
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

Private Declare Function WritePrivateProfileString& Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal AppName$, ByVal KeyName$, ByVal keyDefault$, ByVal FileName$)
Private Declare Function GetPrivateProfileString Lib "kernel32" Alias "GetPrivateProfileStringA" (ByVal AppName As String, ByVal KeyName As Any, keyDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal FileName As String) As Long
'------------------------

AnswerTheMan (accepted answer) wanted me to use regtool5.dll  This is an excellent reference and allows me to access the registry of a win95/98 system with only a few minor draw backs (can't create my own HKEY roots)....it is not working in winNT though and I need it to.  Nothing is written to the nt registry.

service pack shouildnt matter...incidently it is sp3 but I need this to be able to run on any service pack.

Thanks....good solid answer will be rewarded quite generously.  This is a hard question for me to answer but I know most of you guys it is a simple one so I will list this as a moderate +50.
Avatar of Erick37
Erick37
Flag of United States of America image

"Download a ready to use Bas module full of functions to perform common Registry and/or .Ini file operations such as reading, setting, deleting and enumerating values and keys."

http://www.thescarms.com/vbasic/Registry.htm
Avatar of Juilette
Juilette

If it's not here...well who knows?http://www.netfokus.dk/vbadmincode/codevb.html
See http://support.microsoft.com/support/kb/articles/q145/6/79.asp?FR=0 
The module below  is a more extended implementation of what is described in that article in enumaration and expansion.

Attribute VB_Name = "ModReg"
Option Explicit

   Public Const REG_SZ As Long = 1
   Public Const REG_DWORD As Long = 4
   Public Const REG_EXPAND_SZ = 2
   Declare Function ExpandEnvironmentStrings Lib "kernel32" Alias "ExpandEnvironmentStringsA" (ByVal lpSrc As String, ByVal lpDst As String, ByVal nSize As Long) As Long
   Type FILETIME
           dwLowDateTime As Long
           dwHighDateTime As Long
   End Type

   Public Const HKEY_CLASSES_ROOT = &H80000000
   Public Const HKEY_CURRENT_USER = &H80000001
   Public Const HKEY_LOCAL_MACHINE = &H80000002
   Public Const HKEY_USERS = &H80000003

   Public Const ERROR_NONE = 0
   Public Const ERROR_BADDB = 1
   Public Const ERROR_BADKEY = 2
   Public Const ERROR_CANTOPEN = 3
   Public Const ERROR_CANTREAD = 4
   Public Const ERROR_CANTWRITE = 5
   Public Const ERROR_OUTOFMEMORY = 6
   Public Const ERROR_INVALID_PARAMETER = 7
   Public Const ERROR_ACCESS_DENIED = 8
   Public Const ERROR_INVALID_PARAMETERS = 87
   Public Const ERROR_NO_MORE_ITEMS = 259

   Public Const KEY_ALL_ACCESS = &H3F

   Public Const REG_OPTION_NON_VOLATILE = 0

   Declare Function RegCloseKey Lib "advapi32.dll" _
   (ByVal hKey As Long) As Long
   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, phkResult As Long, lpdwDisposition As Long) As Long
   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
   Declare Function RegQueryValueExString Lib "advapi32.dll" Alias _
   "RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As _
   String, ByVal lpReserved As Long, lpType As Long, ByVal lpData _
   As String, lpcbData As Long) As Long
   Declare Function RegQueryValueExLong Lib "advapi32.dll" Alias _
   "RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As _
   String, ByVal lpReserved As Long, lpType As Long, lpData As _
   Long, lpcbData As Long) As Long
   Declare Function RegQueryValueExNULL Lib "advapi32.dll" Alias _
   "RegQueryValueExA" (ByVal hKey As Long, ByVal lpValueName As _
   String, ByVal lpReserved As Long, lpType As Long, ByVal lpData _
   As Long, lpcbData As Long) As Long
   Declare Function RegSetValueExString Lib "advapi32.dll" Alias _
   "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, _
   ByVal Reserved As Long, ByVal dwType As Long, ByVal lpValue As _
   String, ByVal cbData As Long) As Long
   Declare Function RegSetValueExLong Lib "advapi32.dll" Alias _
   "RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, _
   ByVal Reserved As Long, ByVal dwType As Long, lpValue As Long, _
   ByVal cbData As Long) As Long
   Declare Function RegEnumKey Lib "advapi32.dll" Alias "RegEnumKeyA" ( _
      ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpName As String, _
      ByVal cbName As Long) As Long
   Declare Function RegEnumKeyEx Lib "advapi32.dll" Alias "RegEnumKeyExA" ( _
      ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpName As String, _
      lpcbName As Long, lpReserved As Long, ByVal lpClass As String, _
      lpcbClass As Long, lpftLastWriteTime As FILETIME) As Long
   Declare Function RegEnumValue Lib "advapi32.dll" Alias "RegEnumValueA" ( _
      ByVal hKey As Long, ByVal dwIndex As Long, ByVal lpValueName As String, _
      lpcbValueName As Long, lpReserved As Long, lpType As Long, _
      lpData As Byte, lpcbData As Long) As Long
   Declare Function RegQueryInfoKey Lib "advapi32.dll" Alias "RegQueryInfoKeyA" ( _
      ByVal hKey As Long, ByVal lpClass As String, lpcbClass As Long, lpReserved As Long, _
      lpcSubKeys As Long, lpcbMaxSubKeyLen As Long, lpcbMaxClassLen As Long, lpcValues As Long, _
      lpcbMaxValueNameLen As Long, lpcbMaxValueLen As Long, _
      lpcbSecurityDescriptor As Long, lpftLastWriteTime As FILETIME) As Long
     


'***********************************
'********* SetValueEx
'***********************************
Public Function SetValueEx(ByVal hKey As Long, sValueName As String, _
   ltype As Long, vValue As Variant) As Long
       Dim lValue As Long
       Dim sValue As String
       Select Case ltype
           Case REG_SZ
               sValue = vValue + Chr$(0)
               SetValueEx = RegSetValueExString(hKey, sValueName, 0&, _
                                              ltype, sValue, Len(sValue))
           Case REG_DWORD
               lValue = vValue
               Debug.Assert Len(sValueName) > 0 ' That does not work on windows 95
               SetValueEx = RegSetValueExLong(hKey, sValueName, 0&, ltype, lValue, 4)
            Case Else
               Debug.Assert 0
           End Select
   End Function

'***********************************
'********* QueryValueEx
'***********************************
Function QueryValueEx(ByVal lhKey As Long, ByVal szValueName As _
   String, vValue As Variant) As Long
       Dim cch As Long
       Dim lrc As Long
       Dim ltype As Long
       Dim lValue As Long
       Dim sValue As String

       On Error GoTo QueryValueExError

       ' Determine the size and type of data to be read
       lrc = RegQueryValueExNULL(lhKey, szValueName, 0&, ltype, 0&, cch)
       If lrc <> ERROR_NONE Then Error 5

       Select Case ltype
           ' For strings
           Case REG_SZ:
               sValue = String$(cch, 0)
               lrc = RegQueryValueExString(lhKey, szValueName, 0&, ltype, _
                                             sValue, cch)
               If lrc = ERROR_NONE Then
                    If (cch > 1) Then
                        vValue = Left$(sValue, cch - 1)
                    Else
                        vValue = ""
                    End If
               Else
                   vValue = Empty
               End If
           ' For DWORDS
           Case REG_DWORD:
               lrc = RegQueryValueExLong(lhKey, szValueName, 0&, ltype, _
                                          lValue, cch)
               If lrc = ERROR_NONE Then vValue = lValue
           Case REG_EXPAND_SZ:
               sValue = String$(cch, 0)
               lrc = RegQueryValueExString(lhKey, szValueName, 0&, ltype, _
                                             sValue, cch)
               If lrc = ERROR_NONE Then
                   Dim result As String
                   result = String$(2048, 0)
                   Dim size As Integer
                   size = ExpandEnvironmentStrings(Left$(sValue, cch - 1), result, 2048)
                   sValue = Left(result, size)
                   vValue = sValue
               Else
                   vValue = Empty
               End If
           Case Else
               'all other data types not supported
               lrc = -1
       End Select

QueryValueExExit:
       QueryValueEx = lrc
       Exit Function
QueryValueExError:
       Resume QueryValueExExit
   End Function

'***********************************
'********* EnumKey
'***********************************
Public Function EnumKey(ByVal hKey As Long, ByVal index As Long, ByRef key As String) As Long
   Dim cch As Long
   Dim lrc As Long
   Dim ltype As Long
   Dim lValue As Long
   Dim szKeyName As String
   
   cch = 260
   szKeyName = String$(cch, 0)
   lrc = RegEnumKey(hKey, index, szKeyName, cch)
   
   If (lrc = 0) Then
      key = Left$(szKeyName, InStr(szKeyName, Chr$(0)) - 1)
   End If
   
   EnumKey = lrc
End Function


'***********************************
'********* EnumValue
'***********************************
Public Function EnumValue(ByVal hKey As Long, ByVal index As Long, ByRef valueName As String) As Long
   Dim cch As Long
   Dim lrc As Long
   Dim ltype As Long
   Dim lValue As Long
   Dim szValueName As String
   
   'Not tested yet
   Debug.Assert 0
   
   cch = 260
   szValueName = String$(cch, 0)
   lrc = RegEnumValue(hKey, index, szValueName, cch, 0, 0, 0, 0)
   
   If (lrc = 0) Then
      valueName = Left$(szValueName, InStr(szValueName, Chr$(0)) - 1)
   End If
   
   EnumValue = lrc
End Function


'***********************************
'********* SetXXXValue
'***********************************
Public Sub SetXXXValue(ByVal RootKey As Long, ByVal sKeyName As String, ByVal sValueName As String, ByVal ltype As Long, ByVal value As Variant)
    Dim lRetval As Long         'result of the API functions
    Dim hKey As Long         'handle of opened key
    Dim lDispo As Long

    lRetval = RegOpenKeyEx(RootKey, sKeyName, 0, KEY_ALL_ACCESS, hKey)
    If (lRetval <> 0) Then
       lRetval = RegCreateKeyEx(RootKey, sKeyName, 0, "", 0, KEY_ALL_ACCESS, 0, hKey, lDispo)
    End If
    If (lRetval = 0) Then
        lRetval = SetValueEx(hKey, sValueName, ltype, value)
        RegCloseKey (hKey)
    End If
End Sub

Public Sub SetUserValue(ByVal sKeyName As String, ByVal sValueName As String, ByVal ltype As Long, ByVal value As Variant)
   SetXXXValue HKEY_CURRENT_USER, sKeyName, sValueName, ltype, value
End Sub

Public Sub SetMachineValue(ByVal sKeyName As String, ByVal sValueName As String, ByVal ltype As Long, ByVal value As Variant)
   SetXXXValue HKEY_LOCAL_MACHINE, sKeyName, sValueName, ltype, value
End Sub

Public Sub SetClassesValue(ByVal sKeyName As String, ByVal sValueName As String, ByVal ltype As Long, ByVal value As Variant)
   SetXXXValue HKEY_CLASSES_ROOT, sKeyName, sValueName, ltype, value
End Sub

'***********************************
'********* QueryXXXValue
'***********************************

Public Function QueryXXXValue(ByVal RootKey As Long, ByVal sKeyName As String, ByVal sValueName As String) As Variant
    Dim lRetval As Long         'result of the API functions
    Dim hKey As Long         'handle of opened key
    Dim vValue As Variant      'setting of queried value

    lRetval = RegOpenKeyEx(RootKey, sKeyName, 0, KEY_ALL_ACCESS, hKey)
    If (lRetval = 0) Then
      lRetval = QueryValueEx(hKey, sValueName, vValue)
       If Not (lRetval = 0) Then
         vValue = Empty
       End If
        RegCloseKey (hKey)
    End If
   
    QueryXXXValue = vValue
End Function

Public Function QueryUserValue(ByVal sKeyName As String, ByVal sValueName As String) As Variant
   QueryUserValue = QueryXXXValue(HKEY_CURRENT_USER, sKeyName, sValueName)
End Function

Public Function QueryMachineValue(ByVal sKeyName As String, ByVal sValueName As String) As Variant
   QueryMachineValue = QueryXXXValue(HKEY_LOCAL_MACHINE, sKeyName, sValueName)
End Function

Public Function QueryClassesValue(ByVal sKeyName As String, ByVal sValueName As String) As Variant
   QueryClassesValue = QueryXXXValue(HKEY_CLASSES_ROOT, sKeyName, sValueName)
End Function

'***********************************
'********* EnumXXXValues
'***********************************
Public Function EnumXXXValues(ByVal RootKey As Long, ByVal sKeyName As String) As Variant
   Dim i As Long
   Dim nrValues As Long
   Dim lrc As Long
   Dim value As String
   Dim hKey As Long
   Dim AllValuesCollection As New Collection
   Dim lRetval As Long
   Dim vValues() As String
   
   
   On Error GoTo leave
   hKey = 0
   lRetval = RegOpenKeyEx(RootKey, sKeyName, 0, KEY_ALL_ACCESS, hKey)
   If (lRetval = 0) Then
      lrc = 0
      i = 0
      'Request all Values
      While lrc = 0
         lrc = EnumValue(hKey, i, value)
         If (lrc = 0) Then
            i = i + 1
            AllValuesCollection.Add value, "Value" & i
         End If
      Wend
     
      'Copy all Values in a variant array
      If (i > 0) Then
         nrValues = i
         ReDim vValues(nrValues - 1) As String
         For i = 1 To nrValues
            vValues(i - 1) = AllValuesCollection("Value" & i)
         Next
      End If
   End If
   
   'Set return value
   EnumXXXValues = vValues
leave:
    If (hKey <> 0) Then
        RegCloseKey hKey
    End If
End Function

Public Function EnumUserValues(ByVal sKeyName As String) As Variant
   EnumUserValues = EnumXXXValues(HKEY_CURRENT_USER, sKeyName)
End Function

Public Function EnumMachineValues(ByVal sKeyName As String) As Variant
   EnumMachineValues = EnumXXXValues(HKEY_LOCAL_MACHINE, sKeyName)
End Function

Public Function EnumClassesValues(ByVal sKeyName As String) As Variant
   EnumClassesValues = EnumXXXValues(HKEY_CLASSES_ROOT, sKeyName)
End Function

'***********************************
'********* EnumXXXKeys
'***********************************
Public Function EnumXXXKeys(ByVal RootKey As Long, ByVal sKeyName As String) As Variant
   Dim i As Long
   Dim nrKeys As Long
   Dim lrc As Long
   Dim key As String
   Dim hKey As Long
   Dim AllKeysCollection As New Collection
   Dim vKeys() As String
   Dim lRetval As Long
   
   
   
   On Error GoTo leave
   hKey = 0
   lRetval = RegOpenKeyEx(RootKey, sKeyName, 0, KEY_ALL_ACCESS, hKey)
   If (lRetval = 0) Then
      lrc = 0
      i = 0
      'Request all keys
      While lrc = 0
         lrc = EnumKey(hKey, i, key)
         If (lrc = 0) Then
            i = i + 1
            AllKeysCollection.Add key, "Key" & i
         End If
      Wend
     
      'Copy all keys in a variant array
      If (i > 0) Then
         nrKeys = i
         ReDim vKeys(nrKeys - 1) As String
         For i = 1 To nrKeys
            vKeys(i - 1) = AllKeysCollection("Key" & i)
         Next
      End If
   End If
   
   'Set return value
   EnumXXXKeys = vKeys
leave:
    If (hKey <> 0) Then
        RegCloseKey hKey
    End If
End Function

Public Function EnumUserKeys(ByVal sKeyName As String) As Variant
   EnumUserKeys = EnumXXXKeys(HKEY_CURRENT_USER, sKeyName)
End Function

Public Function EnumMachineKeys(ByVal sKeyName As String) As Variant
   EnumMachineKeys = EnumXXXKeys(HKEY_LOCAL_MACHINE, sKeyName)
End Function

Public Function EnumClassesKeys(ByVal sKeyName As String) As Variant
   EnumClassesKeys = EnumXXXKeys(HKEY_CLASSES_ROOT, sKeyName)
End Function

Public Function RegClassesHasSubKeys(ByVal sKeyName As String) As Boolean
   Dim lRetval As Long
   Dim subkeys As Long
   Dim hKey As Long         'handle of opened key
   Dim ft As FILETIME
   Dim Class As String
   Dim cbClass As Long
   Dim cbMaxSubKeyLen As Long
   Dim cbMaxClassLen As Long
   Dim cValues As Long
   Dim cbMaxValueNameLen As Long
   Dim cbMaxValueLen As Long
   Dim cbSecurityDescriptor As Long
   
   RegClassesHasSubKeys = False
   lRetval = RegOpenKeyEx(HKEY_CLASSES_ROOT, sKeyName, 0, KEY_ALL_ACCESS, hKey)
   If (lRetval = 0) Then
      lRetval = RegQueryInfoKey(hKey, Class, cbClass, ByVal 0, subkeys, cbMaxSubKeyLen, cbMaxClassLen, _
                                cValues, cbMaxValueNameLen, cbMaxValueLen, cbSecurityDescriptor, ft)
      If (lRetval = 0) And subkeys > 0 Then
         RegClassesHasSubKeys = True
      Else
         RegClassesHasSubKeys = False
      End If
       RegCloseKey hKey
   End If
End Function

ASKER CERTIFIED SOLUTION
Avatar of manojamin
manojamin

Link to home
membership
This solution is only available to members.
To access this solution, you must be a member of Experts Exchange.
Start Free Trial
<<""AnswerTheMan (accepted answer) wanted me to use regtool5.dll  This is an excellent reference and allows me to access the registry of a win95/98 system with only a few minor draw backs (can't create my own HKEY roots)....it is not working in winNT though and I need it to.  Nothing is written to the nt registry. "">>

well, i'm NT user, and it DOES write to NT registry.
i've just rechecked it.
if you hold RegEdit open as running the code - you have to REFRESH it later....

or - maybe you've tried to write to a non existance key.

anyway - it works on NT, just as on 9x.

Avatar of groone

ASKER

Mirk, I've played a bit with the code you offered and I must admit I have no clue.  Could you give me an example of how to write to a registry and read from a registry with it and we assume all info is being created rather then already existing.

Thanks
Dim keys as variant
Dim k as variant
keys = EnumUserKeys ("Software")

for each k in keys
   debug.print k
next


debug.print QueryUserValue("Software", "")
Avatar of groone

ASKER

and the purple emu hopped through the 6 sided circle.

huh?
Tell me what do you want to do? Give me an example
Avatar of groone

ASKER

Manojamin had the most correct answer in making me think of the security of the nt box.  Put in current user and all worked fine.