isCOBOL Evolve : Appendices : Library Routines : REG : REG_ENUM_KEY, DISPLAY_REG_ENUM_KEY
REG_ENUM_KEY, DISPLAY_REG_ENUM_KEY
The REG_ENUM_KEY library routine enumerates the subkeys of the specified open registry key. It retrieves the name of one subkey each time it is called.
To perform this action on the Windows client machine in an Application Server architecture, use DISPLAY_REG_ENUM_KEY instead of REG_ENUM_KEY.
Syntax:
 CALL "REG_ENUM_KEY" USING openKey 
                           index 
                           name 
                           nameSize
                    GIVING returnCode
Parameters:
openKey
USAGE UNSIGNED-LONG
Specifies the handle to an open registry key.
 
This handle is returned by the REG_CREATE_KEY, REG_CREATE_KEY_EX, REG_OPEN_KEY or REG_OPEN_KEY_EX library routine, or it can be one of the following predefined keys, defined in isreg.def:
 
HKEY_CLASSES_ROOT
HKEY_CURRENT_CONFIG
HKEY_CURRENT_USER
HKEY_LOCAL_MACHINE
HKEY_USERS
HKEY_DYN_DATA
index
USAGE UNSIGNED-LONG
Specifies the index of the subkey of openKey to be retrieved. This value should be 1 for the first call to the REG_ENUM_KEY library routine and then increased incrementally for subsequent calls.
 
Because subkeys are not ordered, any new subkey will have an arbitrary index. This means that the function may return subkeys in any order.
name
PIC X(n)
Receives the name of the subkey, including the terminating null character. This function copies only the name of the subkey, not the full key hierarchy, to the buffer.
nameSize
USAGE UNSIGNED-LONG
Specifies the size of the name parameter
Return code:
returnCode can be any signed numeric data item and provides additional information:
-1
Invalid or missing parameters, or not running on Windows
0
Operation successful.
Non zero
Operation failed. Click here for a list of error codes.
Examples:
Example - Get subkeys list
working-storage section.
copy "isreg.def".
01  open-key-handle         usage unsigned-long.
77  ndx                     pic 9(3).
77  status-code             pic 9(3).
01  subkey-name             pic x(40).
01  name-size               usage unsigned-long.
...
procedure division.
...
get-subkeys.  
    set name-size to size of subkey-name
    perform varying ndx from 1 by 1 until 1 = 2    
       call "reg_enum_key" using  open-key-handle
                                  ndx
                                  subkey-name
                                  name-size
                          giving  status-code
 
       if status-code not = 0  
          exit perform  
       end-if
       display subkey-name
    end-perform