CALL "REG_SET_VALUE_EX" USING openKey type data dataSize [valueName] 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 isreg.def: HKEY_CLASSES_ROOT HKEY_CURRENT_CONFIG HKEY_CURRENT_USER HKEY_LOCAL_MACHINE HKEY_USERS HKEY_DYN_DATA | |
type | USAGE UNSIGNED-LONG | Specifies the type of data pointed to by the data parameter. Valid values, defined in isreg.def are: | |
REG_BINARY | Binary data in any form. | ||
REG_DWORD | A 32-bit number. | ||
REG_DWORD_LITTLE_ENDIAN | A 32-bit number in little-endian format. | ||
REG_DWORD_BIG_ENDIAN | A 32-bit number in big-endian format. | ||
REG_EXPAND_SZ | A null-terminated string that contains unexpanded references to environment variables (for example, "%PATH%"). | ||
REG_LINK | Reserved for system use. | ||
REG_MULTI_SZ | A sequence of null-terminated strings. The following is an example: | ||
String1\0String2\0String3\0LastString\0\0 | |||
The first \0 terminates the first string, the second to the last \0 terminates the last string, and the final \0 terminates the sequence. Note that the final terminator must be factored into the length of the string. | |||
REG_NONE | No defined value type. | ||
REG_QWORD | A 64-bit number. | ||
REG_QWORD_LITTLE_ENDIAN | A 64-bit number in little-endian format. | ||
REG_SZ | A string. | ||
data | PIC X(n) | Specifies the data to be stored. For string-based types, such as REG_SZ, the string must be null-terminated. With the REG_MULTI_SZ data type, the string must be terminated with two null characters. | |
dataSize | USAGE UNSIGNED-LONG | Specifies the size of the information pointed to by the data parameter, in bytes. If the data is of type REG_SZ, REG_EXPAND_SZ, or REG_MULTI_SZ, dataSize must include the size of the terminating null character or characters. | |
valueName | PIC X(n) | Specifies the name of the value to be set. If a value with this name is not already present in the key, the function adds it to the key. If valueName is omitted, the function sets the type and data for the key's unnamed or default value. |
-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). 01 data-type usage unsigned-long. 01 data-size usage unsigned-long. 01 value-name pic x(40). 01 value-data pic x(40). ... procedure division. ... set-value. move reg_sz to data-type move "new-iscobol-value" to value-data inspect value-data replacing trailing spaces by low-value move 1 to data-size inspect value-data tallying data-size for characters before initial x"00" call "reg_set_value_ex" using subkey-handle data-type value-data data-size value-name giving status-code. |