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

Deprecated. Matches the current address loaded via GSDATSET.

Syntax

01 GSID            PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
01 GSOPTIONS       PIC 9(9) BINARY.
*
CALL "GSSFIND" USING GSID, GSOPTIONS, GSFUNSTAT.

Arguments

GSID   Returned by GSINIT for the current instance of GeoStan. Input.

GSFUNSTAT   Return value for the procedure. Output.

GSOPTIONS   The following table contains valid variables. Input.

Processing Instructions

GS-ADDR-CODE

Attempts to standardize and find an address geocode. Set this switch if you want the address parsed and standardized. If this switch is not set, GeoStan uses only the input ZIP and ZIP+4 address elements.

GS-GEO-CODE

Finds a geocode when address standardization is not possible. If GeoStan cannot standardize an address, it uses the input ZIP or ZIP + 4 to find a centroid match.

Search Options

GS-WIDE-SEARCH

Considers all records matching the first letter of the street name, rather than the soundex key on the street name, which allows a wider search. This option has no effect when performing a ZIP centroid match.

GS-FINANCE-SEARCH

GeoStan searches the entire Finance Area for possible streets. This option has no effect when performing a ZIP centroid match.

GS-BUILDING-SEARCH

Enables matching to building names even when no unit numbers are present.

Geocode Levels

GS-Z9-CODE

Attempts to find ZIP+4 centroid match only.

GS-Z7-CODE

Attempts to find ZIP+2 centroid match only (no ZIP + 4 or ZIP).

GS-Z5-CODE

Attempts to find a ZIP centroid match (no ZIP + 4 or ZIP+2).

GS-Z-CODE

Attempts to find a ZIP Code centroid match.

Multi-Line Address Processes

GS-PREFER-POBOX

Sets the preference to a P.O. Box instead of a street address (multi-line input address). See Specifying a preference for street name or P.O. Box for more information. Ignored when processing in CASS mode.

GS-PREFER-STREET

Sets the preference to a street address instead of a P.O. Box (multi-line input address). Ignored when processing in CASS mode.

Reverse Geocoding Processing

GS-NEAREST-ADDRESS

Specifies that GeoStan can match to addresses interpolated on street segments or to point data locations.

GS-NEAREST-INTERSECTION

Specifies that GeoStan can match to intersections.

GS-NEAREST-UNRANGED

Specifies that GeoStan can match a street segment with no number ranges. Enabled with GS-NEAREST-ADDRESS. Ignored for point data and intersection matches.

Note: You can use GS_NEAREST_ADDRESS and GS_NEAREST_UNRANGED together to specify reverse geocoding to both addresses and intersections.

You must use either GS-ADDR-CODE or one of the geocode level options (or both). These option settings are additive. For most purposes, you should specify the GS-ADDR-CODE,GS-GEO-CODE, and one of the geocode level options. If you specify GS-ADDR-CODE and one of the geocode level options, GeoStan returns a ZIP Code centroid match only if the address is standardized but an address geocode is not available.

Return Values

GS-SUCCESS    Found a match.

GS-ERROR    Low-level error; use GSERRGET to retrieve the error information.

GS-ADDRESS-NOT-FOUND    Did not find an address match or you have a metered license and the GeoStan record count is depleted.

GS-ADDRESS-NOT-RESOLVED    GeoStan cannot resolve which possible match is a match.

GS-LASTLINE-NOT-FOUND    Did not find a match for city/state or ZIP Code.

Prerequisites

GSDATSET

Notes

If GeoStan could not standardize an address, you can still retrieve normalized address information, match codes, carrier routes, or other elements with GSDATGET. You can also return alias information by calling GSMGET with an index of 0.

If you enter a pre-parsed address, it must contain the USPS abbreviations for street type, predirectionals, and postdirectionals.

Before each find procedure, call GSCLEAR to reset the internal buffers. If you do not reset the buffers, you may receive incorrect results with information from a previous find.

If you use both the reverse geocode and address line matching variables in the same call, GeoStan displays an error. These types of finds are mutually exclusive.