GSFFST - 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 street object that meets the search criteria.

Syntax

01    GSID                              PIC S9(9) BINARY.
01    GSFUNSTAT                         PIC S9(9) BINARY.
01    STREET-HANDLE                     PIC S9(9) BINARY.
01    GSOPTIONS                         PIC  9(9) BINARY.
01    LOCALE                            PIC X(USER LEN).
01    STREET-NAME                       PIC X(USER LEN).
01    STREET-NUMBER                     PIC X(USER LEN).
*
CALL "GSFFST" USING GSID, STREET-HANDLE, GSOPTIONS, LOCALE, STREET-NAME, STREET-NUMBER, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

STREET-HANDLE    Pointer to a street handle. Returns a valid handle if GeoStan finds a street. Output.

GSOPTIONS   Set the type of search performed by GeoStan. The following table contains the types of searches available. Input.

GS-ZIP-SEARCH

Required. GeoStan searches the ZIP Code specified by LOCALE.

GS-CITY-SEARCH

Required. GeoStan searches the city and state specified by LOCALE.

GS-SDX-SEARCH

Optional. GeoStan searches by soundex. STREET-NAME is a pointer to a numeric soundex key returned by GSSNDX.

LOCALE   Sets the search ares. If GSOPTIONS is set to GS-ZIP-SEARCH, then LOCALE is a valid ZIP Code. If GSOPTIONS is set to GS-CITY-SEARCH, then LOCALE is a valid city and state. Input.

STREET-NAME   Street name, or partial street name, for which to search. If GSOPTIONS is set to GS-SDX-SEARCH, the STREET-NAME is a pointer to a numeric soundex key. Input.

Limits the search to street names that begin with the name string. If STREET-NAME is set to "APPLE," then only streets beginning with Apple are returned, such as Apple or Appleton. If STREET-NAME is not specified, GeoStan finds all the streets specified by LOCALE.

Return Values

GSGS-SUCCESS    Found a match. You can retrieve the data for that match using GSHGET.

GS-NOT-FOUND    Did not find a match.

GS-LASTLINE-NOT-FOUND    Could not find LOCALE.

GS-ERROR    An error occurred; use GSERRGET and GSERRGTX to retrieve more information.

Prerequisites

GSINITWP and GSCLEAR

Notes

You must call GSFFST before GSFFSEG. This procedure also sets the area and criteria for subsequent segment and range searches.

If you are using GSFFST to find a street that has a number as a component of the street name, such as "US HWY 41" or "I-95," enter just the number; the text is not part of the index for such streets.

See Extracting Data from GSD Files for more information on the Find First and Find Next procedures.