isCOBOL Evolve : Appendices : Library Routines : REG : REG_DELETE_VALUE, DISPLAY_REG_DELETE_VALUE
REG_DELETE_VALUE, DISPLAY_REG_DELETE_VALUE
The REG_DELETE_VALUE removes a named value from the specified registry key. Note that value names are not case sensitive.
To perform this action on the Windows client machine in an Application Server architecture, use DISPLAY_REG_DELETE_VALUE instead of REG_DELETE_VALUE.
Syntax:
 CALL "REG_DELETE_VALUE" USING openKey
                               valueName
                        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
valueName
PIC X(n)
The registry value to be removed. If this parameter is NULL or an empty string, the value set by the REG_SET_VALUE library routine is removed.
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 - Delete registry value
working-storage section.
copy "isreg.def".
01  open-key-handle         usage unsigned-long.
77  status-code             pic 9(3).
...
procedure division.
...
delete-value.
   call "reg_delete_value" using open-key-handle
                                 "iscobol-key-value"
                          giving status-code.