GSDATGET - geostan_1 - 2024.01

GeoStan Geocoding Suite Reference for Windows, Linux, and z/OS

Product type
Software
Portfolio
Locate
Product family
GeoStan Geocoding Suite
Product
GeoStan Geocoding Suite > GeoStan
Version
2024.01
Language
English
Product name
GeoStan
Title
GeoStan Geocoding Suite Reference for Windows, Linux, and z/OS
Copyright
2024
First publish date
1994
Last updated
2024-07-29
Published on
2024-07-29T23:01:18.924000

Returns data for all address and matched elements from GeoStan.

Syntax

01 GSID                            PIC S9(9) BINARY.
01 GSOPTIONS                       PIC 9(9) BINARY.
01 GSSWITCH                        PIC 9(9) BINARY.
01 OUTPUT-STRING                   PIC X(USER LEN).
01 OUTLEN                          PIC 9(4) BINARY.
01 GSFUNSTAT                       PIC S9(9) BINARY.
*
CALL "GSDATGET" USING GSID, GSOPTIONS, GSSWITCH, OUTPUT-STRING, OUTLEN, GSFUNSTAT.

Arguments

GSID   ID returned by GSINITWP for the current instance of GeoStan. Input.

GSOPTIONS   Flag indicating whether to retrieve original or processed data. Input.

To retrieve parsed address components, set GSOPTIONS to GS-INPUT. To retrieve matched address information from the parsed input address and the GeoStan database, set GSOPTIONS to GS-OUTPUT.

If the input address does not match, setting GSOPTIONS to GS-OUTPUT returns the address exactly as entered, except for the last line information, which returns only the parsed last line components.

The parsed last line components correspond to the following variables:

GS-LASTLINE

GS-ZIP

GS-ZIP9

GS-CITY

GS-ZIP4

GS-ZIP10

GS-STATE

If there is extra data on the input last line (GS-LASTLINE), this data is not retrievable. For example, in the last line "BOULDER CO 80301 US OF A", "US OF A" is not retrievable from any GSDATGET() procedure.

Note: For valid variables, see Variables for storing and retrieving data.

GSSWITCH   Symbolic constant for the data item to retrieve. Input.

GSFUNSTAT   Return value for the procedure. Output.

OUTPUT-STRING    Location to store the returned data. Output.

OUTLEN   Maximum length of data for GeoStan to return. The COBOL copy member "GEOSTAN" lists as constants the recommended buffer size for each item. These sizes are the maximum lengths required to get the full output string. You can allocate a buffer that is smaller or larger than these values. However, if bufLen is shorter than the returned data, GeoStan truncates the data and does not generate an error. Input.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSSFINDWP

Notes

This procedure retrieves data elements from internal GeoStan buffers for either the original (input) or matched (output) data elements. To retrieve original data, set GSOPTIONS to GS-INPUT. To retrieve matched data, set GSOPTIONS to GS-OUTPUT.