GSFGFX - 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

Finds the first city, county, and or state centroid match from the set of possible matches found.

Syntax

01 GS-GEOGRAPHIC-INFO-EX.
05 GS-INPUT-CITY                             PIC X(39).
05 GS-INPUT-COUNTY                           PIC X(39).
05 GS-INPUT-STATE                            PIC X(20).
05 GS-OUTPUT-CITY                            PIC X(39).
05 GS-OUTPUT-COUNTY                          PIC X(39).
05 GS-OUTPUT-STATE                           PIC X(20).
05 GS-OUTPUT-LAT                             PIC X(11).
05 GS-OUTPUT-LONG                            PIC X(12).
05 GS-OUTPUT-RANK                            PIC X(2).
05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
05 GS-OUTPUT-LOCATION-CODE                   PIC X(5).
05 GS-CLOSE-MATCH-FLAG                       PIC X.
05 GS-INPUT-GEO-LIB-VER-EX                   PIC 9(9) BINARY.
05 GS-OUTPUT-FIPS-CODE                       PIC X(6).            
*
CALL "GSFGFX" USING NAME,.

Arguments

GS-INPUT-CITY    City Name (may be a partial string). Input.

GS-INPUT-COUNTY    County Name (may be a partial string). Optional. Input.

GS-INPUT-STATE    Proper state abbreviation or name for the searched state. Input.

GS-OUTPUT-CITY    Output city. Output.

GS-OUTPUT-COUNTY    Output county. Output.

GS-OUTPUT-STATE    Output state. Output.

GS-OUTPUT-LAT    Returned latitude of the geographic centroid. Output.

GS-OUTPUT-LONG    Returned longitude of the geographic centroid. Output.

GS-OUTPUT-RANK    Returned geographic rank of the city for city centroid. Output.

GS-OUTPUT-RESULT-CODE    Result code equivalent (G3 - city centroid, G2 - country centroid, G1 – state centroid). Output.

GS-OUTPUT-LOCATION-CODE    Location code equivalent (GM - city, GC - county, GS - state). Output.

GS-OUTPUT-GEO-LIB-VER-EX    GeoStan version. Input.

GS-OUTPUT-CLOSE    True indicates a close match. Output.

GS-OUTPUT-FIPS-CODE    FIPS Code. Output.

Return Values

GS-SUCCESS

GS-ERROR

GS-NOT-FOUND

Prerequisites

GSINITWP

Notes

It is recommended that the user first use the Last-line lookup functions to standardize the city, county and state names. This function only performs minimal fuzzy matching on the input city and county names. The location code returned by this function is to provide users with a location code equivalent and is not retrievable using GsDataGet. It is merely provided to offer a consistent label for the type of address match that is returned and will only consist of one of the three Geographic location codes (GM – City, GC – County and GS – State).

Example

Use the following parameter area defined in the COBOL copy member named GEOSTAN filling in the fields with names beginning with GS-INPUT.

01 GS-GEOGRAPHIC-INFO-EX.
05 GS-INPUT-CITY                             PIC X(39).
05 GS-INPUT-COUNTY                           PIC X(39).
05 GS-INPUT-STATE                            PIC X(20).
05 GS-OUTPUT-CITY                            PIC X(39).
05 GS-OUTPUT-COUNTY                          PIC X(39).
05 GS-OUTPUT-STATE                           PIC X(20).
05 GS-OUTPUT-LAT                             PIC X(11).
05 GS-OUTPUT-LONG                            PIC X(12).
05 GS-OUTPUT-RANK                            PIC X(2).
05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
05 GS-OUTPUT-LOCATION-CODE                   PIC X(5).
05 GS-CLOSE-MATCH-FLAG                       PIC X.
05 GS-INPUT-GEO-LIB-VER-EX                   PIC 9(9) BINARY.
05 GS-OUTPUT-FIPS-CODE                       PIC X(6).

For a COBOL coding example, see the example for GSFGF. The call is the same except that there are more output fields returned with GSFGFX.Finds the first geographic information record with partial matching to input names.