Sets a string property.
Note: If you intend to use the same Find property settings for all your address records,
try to construct your application to set the Find properties once before processing.
It is unnecessary to reset the properties again to the same values for each address
record. However, if required, you can change Find property values for individual
searches. Performance may be negatively affected by resetting for individual record
searches. Reset Find properties between address searches only if changing the Find
property value is necessary.
Syntax
01 PROPLIST PIC S9(9) BINARY.
01 PROPENUM PIC S9(9) BINARY.
01 C-CHARACTER-STRING.
05 CHAR-STRING PIC X(user len) VALUE 'your string here'.
05 FILLER PIC X(01) VALUE X'00'.
*
CALL "GSPSETST" USING PROPLIST, PROPENUM, C-CHARACTER-STRING, GSFUNSTAT.
Arguments
PROPLIST Pointer to property list structure. Input and Output.
PROPENUM Property ID. Input.
C-CHARACTER-STRING String value. Input.
GSFUNSTAT Return value for the procedure. Output.
Return Values
GS-SUCCESS
GS-ERROR
Prerequisites
GSPLSTCR