GSFINDWP - 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 a match with user settable match preferences (properties).

Syntax

01 GSID                       PIC S9(9) BINARY.
01 PROPLIST                   PIC 9(9) BINARY.
01 GSFUNSTAT                  PIC 9(9) BINARY.
*
CALL "GSFINDWP" USING GSID, FIND-PROP-LIST, GSFUNSTAT.

Arguments

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

FIND-PROP-LIST    Pointer to property list structure. Input.

GSFUNSTAT   Return value for the procedure. Output.

Conflicting API functions

Detailed here are the categories and categories that conflict in the GSFINDWP properties listed below.

GeoStan applications control the behavior of GSINITWP by setting any of the find properties. Rules exist that control which categories of properties can intermix. The tables below show which property categories conflict. Those categories that are not shown to be in conflict can be used together.

GeoStan detects conflicting properties and returns appropriate error messages from the several GSPSET* functions. This prevents illegal, inconsistent, conflicting, or confusing property combinations from occurring. By guaranteeing fully consistent property lists, this allows the GeoStan engine code to have a clear path to perform the matching logic.

By clearly defining the categories into which the properties fall, and which categories of properties are for use together, this aids in familiarizing you in the semantics and capabilities of the properties. The categories are described below:

Category

Description

Any

No restrictions on the use of this property with other properties. In other words, a property in this category can be used in combination with other properties from a similar property type (init, status, or find).

AnyForward

Find properties that are usable with any use of GSFINDWP which is doing "forward geocoding", that is, standardizing and geocoding an input address.

GeoStanReverse

Find properties that are usable with any use of GSFINDWP which is doing a reverse geocoding search.

GeoStanFindFirstStreet

Find properties that are usable with any use of GSFINDWP which is doing an FindFirstStreet/Segment/Range search.

Custom

Find properties that are usable with any use of GSFINDWP which is using custom find properties.

The properties with the categories listed below in the Category column cannot be used with the properties with categories listed in the Conflicting Category column.

Category

Conflicting category

Any

None.

AnyForward

GeoStanReverse

GeoStanFindFirstStreet

GeoStanReverse

GeoStanFindFirstStreet

Custom

AnyForward

GeoStanFindFirstStreet

Custom

AnyForward

GeoStanReverse

Custom

GeoStanReverse

GeoStanFindFirstStreet

GeoStan does not allow an application to add a property from the category listed in the Category column, if the property list already contains a Match Mode property type listed in the MatchMode value column below:

Category

MatchMode value

Custom

Relax

Interactive

Close

Exact

GeoStanReverse

GeoStanFindFirstStreet

Custom

GSFINDWP Properties

Property Name

Description

GS-FIND-ADDR-POINT-INTERP

Enables address point interpolation. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-ADDRCODE

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. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS

GS-FIND-ADDRESS-RANGE

Enables Map Marker address range geocoding compatibility. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, and Custom.

GS-FIND-ALTERNATE-LOOKUP

Determines whether the preferred lookup is to look for the streets first or the firms first. Default = 3.

•1 - GS-PREFER-STREET-LOOKUP  - Matches to the address line, if a match is not made, then GeoStan matches to the Firm name line.

•2 - GS-PREFER-FIRM-LOOKUP - Matches to the Firm name line, if a match is not made, then GeoStan matches to address line.

•3 - GS-STREET-LOOKUP-ONLY (default) - Matches to the address line.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-APPROXIMATE-PBKEY

When using the Master Location Dataset (MLD), when a match is not made to an MLD record, this feature returns the GS-PB-KEY of the nearest MLD point location. Default = False.

The search radius for the nearest MLD point location can be configured to 0-5280 feet. The default is 150 feet.

This type of match returns a GS-PB-KEY with a leading 'X' rather than a 'P', for example, X00001XSF1IF.

The GS-INIT-OPTIONS-SPATIAL-QUERY init property must be set to True to enable this feature.

For more information, see PreciselyID Fallback

•Category: AnyForward, GeoStanReverse

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, and CASS.

GS-FIND-BUILDING-SEARCH

Controls the ability to search by building name entered in the address line. Enables matching to building names even when no unit numbers are present. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-CENTERLINE-OFFSET

Offset distance from the street center for a centerline match. Values = Any positive integer, which represents number of feet. Default = 0 feet.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet.

•Match modes: Exact, Close, CASS, Relax, Interactive and Custom.

GS-FIND-CENTERLN-PROJ-OF-POINT

Enables GeoStan to keep multiple candidate records when matching with point-level data for use with centerline matching. Default = False.

Not valid when using the reverse geocoding options.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-CLIENT-CRS

Coordinate Reference System. Values = NAD27 and NAD83.

Default = NAD83.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-CLOSEST-POINT

For reverse geocoding, enables matching to the nearest point address within the search radius, rather than to the closest feature (e.g. street segment or intersection as well as point addresses). Default = False.

Note: Requires that at least one streets data set and one points data set are loaded; otherwise, the match will be made to the closest feature.

•Category: GeoStanReverse

•Compatible with: Reverse and Any.

•Conflicts with: GeoStanFindFirstStreet, Custom, AnyForward

•Match modes: Match mode has no impact on reverse geocoding.

GS-FIND-CORNER-OFFSET

Distance, in feet, to offset address-level geocodes from the street end points. If the corner offset distance is more than half the segment length, GeoStan sets the distance to the midpoint of the segment. Default = 50 feet.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-CORRECT-LASTLINE

Corrects the output last line. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-DB-ORDER

List of database index values [starting at 0, separated by semi-colons] indicating which to search and in what order.

If this property is not set, the behavior is to search the DBs in the following order:

–Aux files

–UDs of all types (street and point)

–Point files (Master Location Data, TomTom Points and HERE Points)

–GSD (TomTom and HERE)

–GSD (TIGER)

–GSD (USPS)

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-DPV

Turn on DPV mode. Default = True.

•Category: AnyForward

•Compatible with: AnyForward, Any, Custom.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-EXPAND-SEARCH-RADIUS

Distance, in feet, to use for the expanded search radius. Default = 132000.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-EXPND-SRCH-LIM-TO-STA

Do not cross state boundaries when doing an expanded search. Default = True.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-FIRST-LETTER-EXPANDED

Enables extra processing for bad first letter (missing, wrong, etc.). Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Custom, and CASS. Ignored in Exact mode.

GS-FIND-LACSLINK

Turns on LACSLink mode. Default = True.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-MATCH-CODE-EXTENDED

Enables the return of additional address match information. Most notably, this is used to indicate whether or not an exact match was made to the input unit number. An address match is still returned if there is not an exact match to the input unit number, but the match is to the main building address without units. This extended match code digit will also provide information about any changes in the house number, unit number and unit type fields. In addition, it can indicate whether there was address information that was ignored. For more information, see Understanding Extended Match Codes. Default = False.

•Category: AnyForward

•Compatible with: AnyForward, Any, Custom.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-MATCH-MODE

Controls the closeness-of-match rules used for matching in GSFINDWP.

This property affects how GsDataSet performs, specifically how the input address is parsed. For this reason, only alter this find property before calling GsDataSet to input the address and lastline data. If you alter this property after calling GsDataSet, the results of the subsequent find will be unpredictable. Default = GS-MODE-CLOSE.

GS-MODE-EXACT: Requires an exact name match. Generates the fewest number of possibles to search.

GS-MODE-CLOSE: Requires a very close name match. Generates a moderate number of possibles to search

GS-MODE-RELAX: Requires a close name match. Generates a large number of possibles to search.

GS-MODE-INTERACTIVE: For singleline address matching only. Allows for more flexible matching patterns and may, in some cases, return additional possible matches than Relax match mode.

GS-MODE-CASS: Requires a close name match. Generates a modest number of possibles to search. This setting imposes additional rules to ensure compliance with the USPS regulations for CASS software. For example, this mode disables intersection matching, and matching to the User Dictionary matches for standardization

GS-MODE-CUSTOM: Allows applications to specify individual "must match" field matching rules for address number, address line, city, ZIP Code, state.

Note: Not supported in singleline address matching.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet. In reverse geocoding, this setting is ignored.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-MIXED-CASE

Returns results in mixed case. Default = False.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: none.

•Match modes: Relax, Interactive, Close, Exact, Custom and CASS.

GS-FIND-MUST-MATCH-ADDRNUM

Candidates must match house number exactly. Default = True.

•Category: Custom

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, and GeoStanFindFirstStreet.

•Match modes: Custom

Note: Custom match mode and the Must Match settings are not supported in singleline address matching.

GS-FIND-MUST-MATCH-CITY

Candidates must match city. Default = False.

•Category: Custom

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Custom

Note: Custom match mode and the Must Match settings are not supported in singleline address matching.

GS-FIND-MUST-MATCH-MAINADDR

Candidates must match main address exactly. Default = False.

•Category: Custom

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Custom

Note: Custom match mode and the Must Match settings are not supported in singleline address matching.

GS-FIND-MUST-MATCH-STATE

Candidates must match state. Default = False.

•Category: Custom

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Custom

Note: Custom match mode and the Must Match settings are not supported in singleline address matching.

GS-FIND-MUST-MATCH-ZIPCODE

Candidates must match ZIP Code. Default = False.

•Category: Custom

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Custom

Note: Custom match mode and the Must Match settings are not supported in singleline address matching.

GS-FIND-NEAREST-ADDRESS

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

You can use GS-FIND-NEAREST-ADDRESS and GS-FIND-NEAREST-INTERSECTION together to specify reverse geocoding to both addresses and intersections.

For reverse geocoding, you need to set the reverse geocoding processing find properties: GS-FIND-NEAREST-ADDRESS, GS-FIND-NEAREST-INTERSECTION, and/or GS-FIND-NEAREST-UNRANGED. The address processing and multi-line address processing options are not valid for reverse geocoding.

•Category: GeoStanReverse

•Compatible with: Reverse and Any.

•Conflicts with: GeoStanFindFirstStreet, Custom, AnyForward

•Match modes: Reverse geocoding doesn't use match modes - valid for all match modes.

GS-FIND-NEAREST-INTERSECTION

Specifies that GeoStan can match to intersections. Default = False.

You can use  GS-FIND-NEAREST-INTERSECTION and GS-FIND-NEAREST-ADDRESS together to specify reverse geocoding to both addresses and intersections.

For reverse geocoding, you need to set the reverse geocoding processing find properties:

GS-FIND-NEAREST-INTERSECTION, GS-FIND-NEAREST-ADDRESS, and/or GS-FIND-NEAREST-UNRANGED.

The address processing and multi-line address processing options are not valid for reverse geocoding.

•Category: GeoStanReverse

•Compatible with: Reverse and Any.

•Conflicts with: GeoStanFindFirstStreet, Custom, AnyForward

•Match modes: Reverse geocoding doesn't use match modes - valid for all match modes.

GS-FIND-NEAREST-UNRANGED

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

•Category: GeoStanReverse

•Compatible with: Reverse and Any.

•Conflicts with: GeoStanFindFirstStreet, Custom, AnyForward

•Match modes: Reverse geocoding doesn't use match modes - valid for all match modes.

GS-FIND-POINT-ZIP-MATCH

Enables point ZIP matching. Default = False.

•Category: AnyForward

•Compatible with: AnyForward andAny.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, and CASS.

GS-FIND-PREFER-POBOX

Sets the preference to P.O. Box addresses instead of street addresses for multi-line input addresses. See "Specifying a preference for street name or P.O. Box" on page 36 for more information. Ignored if processing in CASS mode. Default = False.

If both GS-FIND-PREFER-POBOX and GS-FIND-PREFER-STREET are set to True, then they are ignored and the default, GS-FIND-PREFER-STREET is used.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-PREFER-STREET

Sets the preference to street addresses instead of P.O. Box addresses for multi-line input addresses. Ignored if processing in CASS mode. Default = False.

If both GS-FIND-PREFER-POBOX and GS-FIND-PREFERSTREET are set to True, then they are ignored and the default, GS-FIND-PREFER-STREET is used.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse, GeoStanFindFirstStreet and Custom.

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-PREFER-ZIP-OVER-CITY

Prefer candidates matching input ZIP over matches to input city. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Close, Exact, and Custom. Ignored for Interactive and CASS match modes. Interactive match mode returns the best address regardless of this setting.

GS-FIND-RET-INTERSECTION-NUM

Returns intersection numbers. Default = False.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, and CASS.

GS-FIND-SEARCH-AREA

Assists in finding a match when the input address contains limited or inaccurate city or ZIP Code information. Default = 0.

0 - GS-FIND-SEARCH-AREA-CITY - Searches the specified city.

1 - GS-FIND-SEARCH-AREA-FINANCE - Searches the entire Finance Area for possible streets.

This option has no effect when performing a ZIP centroid match.

2 - GS-FIND-SEARCH-AREA-EXPANDED - This value effectively has two options that can be set:

Allows the setting of the radius in miles (up to 99) around which your record lies. The default radius setting is 25 miles.

Allows for limiting the search to the state. The default setting is True.

•Category: Any

•Compatible with: Any, AnyForward, GeoStanReverse, and GeoStanFindFirstStreet.

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, and Custom. Search area cannot be changed in CASS match mode.

GS-FIND-SEARCH-DIST

Radius, in feet, that GeoStan searches for a reverse geocode match. The range is 0 - 5280 feet. Default = 150 feet.

GS-FIND-SEARCH-DIST is also used for the Predictive Lastline and PreciselyID Fallback features in forward geocoding.

•Category: GeoStanReverse

•Compatible with: GeoStanReverse and Any.

•Conflicts with: GeoStanFindFirstStreet, and AnyForward (see the note above for the exceptions for use in forward geocoding).

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-STREET-CENTROID

Turns on street locator geocoding. Default = False.

•Category: AnyForward

•Compatible with: AnyForward, Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet..

•Match modes: Relax, Interactive, Close, Exact, and Custom.

GS-FIND-STREET-OFFSET

Left and right offset distance from the street segments. The range is 0 - 999 feet. Default = 50 feet.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse, and GeoStanFindFirstStreet..

•Conflicts with: None.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-SUITELINK

Enables SuiteLink mode. Default = True.

•Category: AnyForward

•Compatible with: AnyForward, and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Custom and CASS. Exact match mode ignores this setting.

GS-FIND-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. Default = False.

This option has no effect when performing a ZIP centroid match.

•Category: Any

•Compatible with: AnyForward, Any, Custom, GeoStanReverse and GeoStanFindFirstStreet.

•Conflicts with: none.

•Match modes: Relax, Interactive, Close, and Exact.

GS-FIND-Z-CODE

Attempts to find any ZIP centroid match. Default = False.

Not valid when using the reverse geocoding options.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-Z5-CODE

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

Not valid when using the reverse geocoding options.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-Z7-CODE

Attempts to find a ZIP+2 centroid match only (no ZIP + 4 or ZIP). Default = False.

Not valid when using the reverse geocoding options.

•Category: AnyForward

•Compatible with: AnyForward and Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

GS-FIND-Z9-CODE

Attempts to find a ZIP + 4 centroid match only. Default = False.

Not valid when using the reverse geocoding options.

•Category: AnyForward

•Compatible with: AnyForwardand Any.

•Conflicts with: GeoStanReverse and GeoStanFindFirstStreet.

•Match modes: Relax, Interactive, Close, Exact, Custom, and CASS.

The following table lists the properties that can be set using GSFINDWP.

Return Value

GS-ERROR

GS-SUCCESS

Prerequisites

GSPLSTCR and GSPSET*

Notes

The application owns the property list, but GeoStan is the active user.

Do not destroy the property list by calling GSPLSTDE while GeoStan is still using that property list.