CALL "REG_SET_VALUE" USING openKey value [subKey] GIVING returnCode |
openKey | USAGE UNSIGNED-LONG | Specifies the handle to an open registry key. The calling process must have KEY_SET_VALUE access to the 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 iscoblib.def: HKEY_CLASSES_ROOT HKEY_CURRENT_CONFIG HKEY_CURRENT_USER HKEY_LOCAL_MACHINE HKEY_USERS HKEY_DYN_DATA |
value | PIC X(n) | Specifies the value to be stored. |
subKey | PIC X(n) | Specifies the name of a subkey of the openKey parameter. The function sets the default value of the specified subkey. Key names are not case sensitive. If this parameter is omitted, the function sets the default value of the key identified by openKey. |
-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. |
working-storage section. 01 subkey-handle usage unsigned-long. 77 status-code pic 9(3). 77 value-data pic x(50). ... procedure division. ... set-key-value. move "iscobol-value" to value-data call "reg_set_value" using subkey-handle value-data giving status-code. |