Returns information about current GeoStan data set and license.
Syntax
01 GSID PIC S9(9) BINARY.
01 OPTION PIC S9(9) BINARY.
01 GSFUNSTAT PIC 9(9) BINARY.
01 OUTLEN PIC 9(9) BINARY.
01 OUTPUT-STRING PIC X(USER LEN).
*
CALL "GSFSTATX" USING GSID, OPTION, OUTPUT-STRING, OUTLEN, GSFUNSTAT.
Arguments
GSID ID returned by GSINITWP for the current instance of GeoStan. Input.
OPTION Specific information to return. The following table includes the types of information available. Input.
GS-STATUS-DATATYPE-NUM |
GS-SUCCESS or GS-ERROR.GeoStan places the retrieved information in the buffer. See the Return Values section of this procedure for the returned numeric values. |
GS-STATUS-DATATYPE-STR |
GS-SUCCESS or GS-ERROR. GeoStan places this information in the buffer. |
GS-STATUS-DATUM-NUM |
Numeric values listed in the Return Values section of this procedure. |
GS-STATUS-DATUM-STR |
The NAD used natively by the data. It does not reflect the datum currently in use by GeoStan. See GSGDATUM and GSSDATUM for further information on setting the returned NAD. |
GS-STATUS-DAYS-REMAINING |
•DAYS-UNLIMITED or the number of days remaining before the expiration of the license for unmetered licenses and unlimited licenses. •Days remaining before license expiration for metered limited licenses. |
GS-STATUS-FILE-CHKSUM-NUM |
Calculated value (an integer) used to check data integrity. The OUTPUT-STRING and OUTLEN parameters are unused. Set OUTLEN to 0. |
GS-STATUS-GEO-RECORD-TOTAL |
•0 for unmetered licenses. •Total number or records geocoded for metered licenses |
GS-STATUS-RECORDS-REMAINING |
•RECORDS-UNLIMITED for unmetered licenses and metered unlimited licenses. •Number or records remaining on the license for metered limited licenses |
GSFUNSTAT Return value for the procedure. Output.
OUTLEN Maximum size of 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.
OUTPUT-STRING The location to store the returned data. Output.
Return values
The following table shows the return values for the GS-STATUS-DATATYPE-NUM mode.
GS-STATUS-DATATYPE-NUM |
Data Type |
---|---|
0 |
USPS |
1 |
TIGER |
2 |
TomTom street-level data |
4 |
Deprecated |
6 |
HERE (formerly NAVTEQ) street-level data |
7 |
TomTom point-level data |
9 |
Auxiliary file |
10 |
User Dictionary |
11 |
HERE (formerly NAVTEQ) point-level data |
12 |
Master Location Data |
The following table shows the return values for the GS-STATUS-DATUM-STR mode.
GS-STATUS-DATUM-STR |
Data Type |
---|---|
0 |
NAD27 |
1 |
NAD83 (WGS84 for GTD data) |
Prerequisites
GSINITWP