GSMGET - 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 the address elements for the match candidate item specified.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

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

GSOPTIONS   Variable for the argument you want to retrieve. Input.

INDEX   Entry number (0-based) of the possible match. Input.

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

OUTLEN   Maximum size of the data GeoStan returns. If OUTLEN is shorter than the data returned by GeoStan, GeoStan truncates the data and does not generate an error. Input.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSNMULT

Notes

This procedure retrieves data from the GeoStan buffer for match candidates. GeoStan indicates a match candidate as the GSSFINDWP GS-ADDRESS-NOT-RESOLVED return code. It is important to first test for an intersection match, since the variables are different for retrieving intersection and non-intersection matches.

When using any street name variable (GS-NAME, GS-PREDIR, GS-POSTDIR, GS-TYPE) the additional modifier GS-ALIAS is available to request specific alias information, rather than preferred name information. For example, in Boulder, CO, Wallstreet is an alias for Fourmile Canyon. The address 123 Wallstreet, Boulder CO 80301 matches to 123 Fourmile Canyon Dr.

MOVE GS-NAME TO GSOPTIONS.CALL "GSMGET" USING GSID, GSOPTIONS, ...

Returns "FOURMILE CANYON" in OUTPUT-STRING

MOVE GS-ALIAS TO GSOPTIONS.ADD GS-NAME TO GSOPTIONS.CALL "GSMGET" USING GSID, GSOPTIONS, ...

Returns "WALLSTREET" in OUTPUT-STRING.

If you use GS-ALIAS with an variable that does not return alias information (such as GS-ZIP), GeoStan returns the information in the normal format. If GS-IS-ALIAS returns A07, you can only get information based on the returned address, not the alias.