Retrieves data for objects found via GSSFFSG and GSFNRANG.
Syntax
01 GSID PIC S9(9) BINARY.
01 GSFUNSTAT PIC S9(9) BINARY.
01 RANGE-HANDLE PIC S9(9) BINARY.
01 GSOPTIONS PIC 9(9) BINARY.
01 OUTPUT-STRING PIC X(USER LEN)
01 OUTLEN PIC S9(4) BINARY.
CALL "GSHGET" USING GSID, GSOPTIONS, RANGE-HANDLE,OUTPUT-STRING, OUTLEN, GSFUNSTAT.
Arguments
GSID ID returned by GSINITWP for the current instance of GeoStan. Input.
GSFUNSTAT Return value for the procedure. Output.
RANGE-HANDLE Pointer to the current range handle. Input.
GSOPTIONS Variable for the argument you want to retrieve. Input.
OUTPUT-STRING Location to store the returned data. Output.
OUTLEN Maximum size of the data that GeoStan returns. If OUTLEN is shorter than the data returned by GeoStan, GeoStan truncates the data and does not generate an error. Input.
Return Values
GS-SUCCESS
GS-ERROR
Prerequisites
GSFFSEG
or GSFNRANG
Notes
This procedure retrieves data from the geocode buffer for a given range handle. If you have a street or segment handle, you must convert the handle to a range handle before you can use this procedure.