Deprecated COBOL procedures

GSSFIND

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.

GSGCRD

Deprecated. Retrieves coordinates for the street segment found via GSSFIND.

Syntax

01 GSID         PIC S9(9) BINARY.
01 GSFUNSTAT         PIC 9(4) BINARY.
01 COORDS         OCCURS 64 TIMES.
05 COORD-X         PIC S9(9) BINARY.
05 COORD-Y         PIC S9(9) BINARY.
01 MAXPOINTS         PIC 9(4) BINARY.
*
CALL "GSGCRD" USING GSID, COORDS, MAXPOINTS, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

COORDS   Array of coordinates, in x,y (longitude, latitude) order. Output.

MAXPOINTS   Maximum number of points that GSGCRD should return; used to prevent writing past the end of COORDS buffer. Input.

Return Values

Number of points assigned to buffer.

Prerequisites

GSSFIND

Notes

This procedure returns an array of coordinates for the current feature found via GSSFIND. The maximum number that GeoStan can return is 64 coordinate pairs, each pair consisting of two long integers.

GeoStan scales coordinate pairs to integers with four decimal digits of precision. Thus, GeoStan returns a point at (-98.3, 29.7) as (983000, 297000). This is a different scale from that expected by Spatial+ and similar GIS applications, which typically express coordinates in millionths of degrees. You may need to scale coordinates obtained with this procedure before using them as input to other software libraries or applications.

GSGDATUM

Deprecated. Returns the current datum setting.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

Returns the current datum setting. Valid settings are DATUM-NAD27 and DATUM-NAD83.

Prerequisites

GSSDATUM

Notes

This procedure returns the datum currently used by GeoStan in calculating address coordinates. This setting affects only the numeric coordinates returned by GSDATGET for the latitude and longitude of an address.

A datum is a mathematical model of the Earth used to calculate the coordinates on any map, chart, or survey system. The North American Datum (NAD) is the official reference ellipsoid used for the primary geodetic network in North America.

Although the return values are DATUM_NAD27 and DATUM_NAD83, note that GTD uses WGS84 instead of NAD83. These two coordinate systems are compatible.

GSHGCRD

Deprecated. Retrieves the coordinates for a street segment object found via GSFFSEG and GSFNRANG.

Syntax

01 GSID                      PIC S9(9) BINARY.
01 GSFUNSTAT                 PIC S9(9) BINARY.
01 SEGMENT-HANDLE            PIC S9(9) BINARY.
01 MAXPOINTS                 PIC  9(4) BINARY.
01 COORDS                    OCCURS <nnn> TIMES.
05 COORD-X            PIC S9(9) BINARY.
05 CORRD-Y            PIC S9(9) BINARY.
*
CALL "GSHGCRD" USING GSID, SEGMENT-HANDLE, COORDS, MAXPOINTS, GSFUNSTAT.

Arguments

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

GSFUNSTAT   return value for the procedure. Output.

SEGMENT-HANDLE    Handle of the segment object for the returned coordinates. Input.

COORDS   Array of coordinates, in x,y (longitude, latitude) order. Output.

MAXPOINTS   Maximum number of points that GSGCRD returns; used to prevent writing past the end of COORDS buffer. Input.

Return Values

Number of points assigned to the buffer.

Prerequisites

GSFFSEG or GSFNRANG

Notes

This procedure returns an array of coordinates for the segment identified in SEGMENT-HANDLE.

GSINIT

Deprecated. Initializes GeoStan.

Syntax

01 GSID            PIC S9(9) BINARY.
01 LSTATUS         PIC  9(9) BINARY.
01 GSOPTIONS       PIC  9(9) BINARY.
* PPATH AND Z4DIR: ONLY VALID VALUES ARE BLANK OR "HIPER"
* THEY ARE ONLY USED IN GSINIT
*
01 PPATH           PIC X(12).
01 Z4DIR           PIC X(12).
*
CALL "GSINIT" USING GSOPTIONS, PPATH, Z4DIR, LSTATUS, GSID.

Arguments

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

GSOPTIONS   Specifies which components of GeoStan to initialize.

GS-FILE-ADDR-CODE

Loads the files necessary for address geocoding.

GS-FILE-Z9-CODE

Loads the Z9 file for centroid geocoding.

GS-FILE-SPATIAL-QUERY

Loads spatial query files. If GeoStan cannot load the spatial query files, GSINIT fails. You can verify that GeoStan loads the files by checking the LStatus parameter in GSINIT.

Except for a few cases, you should always specify GS-FILE-ADDR-CODE and GS-FILE-Z9-CODE. Input.

PPATH   List of paths to search for necessary files. Set this argument to either " " or to "HIPER", which loads the GSD file into hyperspace (OS/390 extended memory). Other values are ignored. Input.

Z4DIR   Name of the ZIP + 4 directory file. Set this argument to either " " or to "HIPER", which loads the Z9 file into hyperspace (OS/390 extended memory). GeoStan ignores other values. Input.

LSTATUS   Pointer to a long integer that specifics which components GeoStan successfully initialized. Output.

GeoStan uses the following constants to test each significant bit:

GS-FILE-CBSA-DIR

Successfully loaded The CBSA lookup file (cbsac.dir).

GS-FILE-CITY-DIR

Successfully loaded the City lookup file (Ctyst.dir).

GS-FILE-EWS

Successfully loaded the EWS file (ews.txt).

GS-FILE-EXPIRED

All GSD files have expired (see Return Values section below).

GS-FILE-AUXILIARY

Successfully loaded the auxiliary file (.gax).

GS-FILE-GEO-DIR

Successfully loaded the GeoStan directory file (*.gsd).

GS-FILE-LICENSE

Successfully loaded the GeoStan license file.

GS-FILE-LOT

Successfully loaded the eLOT and Z4Change file (Us.gsl)

GS-FILE-PARSE-TABLES

Successfully loaded the parsing tables (Parse.dir).

GS-FILE-SPATIAL-QUERY

Successfully loaded the spatial query file (finmbr.dat).

GS-FILE-ZIP4-CENT-DIR

Successfully loaded the ZIP + 4 centroid file (Z4.dir).

GS-FILE-ZIPMOVE

Successfully loaded the ZIPMove file (Us.gsz).

GS-FILE-ZIP9-IDX

Successfully loaded the ZIP9 index file (Zip9.gsu).

Return Values

Returns a valid GSID if the system initializes correctly.

Returns 0 if GeoStan did not initialize.

GSINIT can fail for any of the following reasons:

  • GeoStan did not find the necessary files. Check LSTATUS for the files GeoStan successfully found (and by omission, the files not found).

  • Not enough memory for GeoStan to initialize.

  • All available GSD files have expired. In this situation, GSINIT returns GS-FILE-EXPIRED in the LSTATUS argument.

Prerequisites

GSSLIC

Notes

Must be called before GSSCACHE, GSSLIC, or GSSRELD.

If you are using the GSSCACHE and GSSRELD procedures, You must call these before GSINIT.

You must call GSINIT before any other GeoStan procedure that uses the handle that GSINIT returns.

GSDPVINR

Deprecated. Initializes GeoStan for DPV.

Syntax

01 GSID               PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 STRUCT-SIZE        PIC S9(9) BINARY.
01 W-HAVE-MESSAGE     PIC S9(9) BINARY VALUE +0.
01 W-ERROR-MSG        PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL     PIC X(256) VALUE LOW-VALUES.
*
CALL 'GSDPVINR' USING GSID, GS-DPV-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.

Arguments

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

GS-DPV-INIT-STRUCT    Also defined in GEOSTAN.H. This structure contains the following:

GS-DIS-STRUCT-VERSION    Set to GS-GEOSTAN-VERSION. Input.

GS-DIS-OPTIONS    Reserved for future implementation. Input.

GS-DIS-PDIRECTORY    String [GS-MAX-STR-LN] that specifies the directory containing the DPV file. Input.

GS-DIS-SECURITY-KEY    Security key to initialize DPV functionality. Input.

GS-DIS-STATUS    Indicates the successful initialization of DPV. the following table contains the constants used to test each significant bit. Output.

GS-DPV-FILE-SECURITY

The DPV security file for initializing the DPV functionality.

GS-DPV-FILE-ALL

The DPV data initialized successfully.

GS-DIS-DATA-ACCESS    Indicates the type of files to load and how to access the files. The following table contains the possible values. Input.

DPV-DATA-FULL-FILEIO

Default. dpvh.db accessed via file I/O and Micro (U) memory model.

Use this option for OS/390.

DPV-DATA-FULL-MEMORY

dpvh.db loaded completely into memory and Huge (H) memory model (about 1.3 GB). Use this option to gain performance improvement by reducing repetitive file I/O.

DPV-DATA-SPLIT-FILEIO

dpvs.db accessed via file I/O and Micro (U) memory model. Separates the DPV data file into multiple smaller files, based on the first 2 digits of the ZIP Code. If you sort your mailing file by ZIP Code, you can bring the relevant portion of the DPV file into memory. This process uses 32 MB of storage, but reduces the number of I/O requests that normally occurs when you use the full DPV data file. Use this option if your file is sorted by ZIP Code and you have limited memory.

DPV-DATA-SPLIT-MEMORY

dpvs.db loaded completely into memory and Huge (H) memory model (about 965 MB)

DPV-DATA-FLAT-FILEIO

dpv.db accessed via file I/O and Micro (U) memory model.

DPV-DATA-FLAT-MEMORY

dpv.db Large (L) memory model (about 70 MB). This configuration will provide the best performance overall.

GS-DIS-MEMORY-BUFFER-SIZE    Number of megabytes used to load buffered files into memory. Input.

This option is only valid if dataAccess!= DPV-DATA-FULL-MEMORY. The following are possible values:

0

Default. Do not load DPV files into memory. Access is through file I/o.

Note: Use this option for OS/390.

1-999

Number of megabytes to allocate for buffered I/o.

DPV-DATA-SPLIT-FILEIO

Use if your file is sorted by ZIP Code and you have limited memory. Uses a split data format that separates the DPV data file into multiple smaller files, based on the first 2 digits of the ZIP Code. If you sort your mailing file by ZIP Code, you can use this value to bring the relevant portion of the DPV file into memory. This process uses 32 MB of storage, but reduces the number ofI/O requests that normally occurs when you use the full DPV data file.

STRUCT-SIZE   The size of the DPVINITSTRUCT data structure. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-ERROR   Call GSERRGTX for more information

GS-WARNING   Call GSERRGTX for more information

Prerequisites

GSINIT

Example

First initialize GeoStan for DPV.

**** WORKING STORAGE VARIABLES ******************
01 GSID               PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 STRUCT-SIZE        PIC S9(9) BINARY.
01 W-HAVE-MESSAGE     PIC S9(9) BINARY VALUE +0.
01 W-ERROR-MSG        PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL     PIC X(256) VALUE LOW-VALUES.
 
COPY GSCONST.
 
**** SAMPLE CODE TO INITIALIZE DPV **************
**** PLACE AFTER CALL TO GSINIT    **************
MOVE '(YOUR DPV LICENSE KEY)' TO GS-DIS-SECURITY-KEY.
MOVE GS-GEOSTAN-VERSION       TO GS-DIS-STRUCT-VERSION.
MOVE DPV-DATA-FULL-FILEIO     TO GS-DIS-DATA-ACCESS.
MOVE ZERO                     TO GS-DIS-MEMORY-BUFFER-SIZE.
MOVE GS-DPV-COB-STRUCT-SIZE   TO STRUCT-SIZE.
MOVE 'NULL' TO GS-DIS-PDIRECTORY.
MOVE X'00' TO GS-DIS-PDIRECTORY(5:1).
 
CALL 'GSDPVINR' USING GSID, GS-DPV-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.
 
IF GSFUNSTAT = GS-SUCCESS
DISPLAY 'DPV INITIALIZED SUCCESSFULLY'
ELSE
DISPLAY '********************************'
DISPLAY 'DPV FAILED TO INITIALIZE'
DISPLAY 'GSFUNSTAT IS:', GSFUNSTAT
DISPLAY 'GSID IS:', GSID
DISPLAY 'GS-DPV-INIT-STRUCT IS:', GS-DPV-INIT-STRUCT
DISPLAY 'STRUCT-SIZE IS:', STRUCT-SIZE
DISPLAY '********************************'
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
PERFORM UNTIL W-HAVE-MESSAGE IS EQUAL TO ZERO
CALL 'GSERRGTX' USING GSID, W-ERROR-MSG, W-ERROR-DETAIL, GSFUNSTAT
DISPLAY 'W-ERROR-MSG:', W-ERROR-MSG
DISPLAY 'W-ERROR-DETAIL:', W-ERROR-DETAIL
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
END-PERFORM.

After you have initialized DPV and called GSSFIND for an address, you can then call GSDATGET and request any of the following output fields, which are included in the copy member GSCONST:

• GS-DPBC

•GS-DPV-CONFIRM

•GS-DPV-CMRA

• GS-DPV-FALSE-POS

• GS-DPV-FOOTNOTE1

• GS-DPV-FOOTNOTE2

•GS-DPV-FOOTNOTE3

•GS-DPV-FOOTNOTE4

•GS-DPV-FOOTNOTE5

•GS-DPV-FOOTNOTE6

GSSDATUM

Deprecated. Specifies the datum GeoStan uses to calculate address coordinates.

Syntax

01 GSID               PIC 9(09) BINARY.
01 NEWDATUM               PIC 9(09) BINARY.
01 GSFUNSTAT               PIC S9(09) BINARY.
*
CALL "GSSDATUM" USING GSID, NEWDATUM, GSFUNSTAT.

Arguments

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

NEWDATUM   Variable value indicating the datum to use in returning address coordinates. Valid variables are DATUM-NAD87 and DATUM-NAD83. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS    GeoStan used the requested datum to calculated the existing coordinates (no conversion required), or the files for the requested datum were present.

GS-ERROR    Did not find all of the files for the requested datum. GeoStan does not reset the datum, and continues to use the current datum. Call GSERRGET to find the datum files that were not loaded.

Prerequisites

GSINIT

Notes

A datum is a mathematical model of the Earth used to calculate the coordinates on any map, chart, or survey system. The North American Datum (NAD) is the official reference ellipsoid used for the primary geodetic network in North America.

Use GSSDATUM to select the datum you want GeoStan to use when returning address coordinates via GSDATGET.

You must call GSSDATUM before calling GSSFIND to ensure that the lat and lon values are cached and are not modified.

This setting affects only the numeric coordinates returned by GSDATGET for the latitude and longitude of an address.

Although the arguments are DATUM_NAD27 and DATUM_NAD83, note that GTD uses WGS84 instead of NAD83. These two coordinate systems are compatible.

GSLACINR

Deprecated. Initialize GeoStan for LACSLink.

Syntax

01 GSID            PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT       PIC S9(9) BINARY.
01 STRUCT-SIZE     PIC S9(9) BINARY.
01 W-HAVE-MESSAGE  PIC S9(9) BINARY.
01 W-ERROR-MSG     PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL  PIC X(256) VALUE LOW-VALUES.
*
CALL 'GSLACINR' USING GSID, GS-LACSLINK-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.

Arguments

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

GS-LACSLINK-INIT-STRUCT    Also defined in GEOSTAN.H. This structure contains the following:

GS-LIS-STRUCT-VERSION    LACSLink version number. Set to GS-GEOSTAN-VERSION. Input.

GS-LIS-OPTIONS    Reserved for future implementation. Input.

GS-LIS-STATUS    Indicates the successful initialization of LACSLink. The following table contains the constants used to test each significant bit. Output.

GS-LACSLINK-FILE-LICENSE

LACSLink license loaded successfully.

GS-LACSLINK-FILE-ALL

LACSLink data loaded successfully.

GS-LIST-SECURITY-KEY    Security key to initialize LACSLink functionality. Input.

STRUCTSIZE   Size of the LACSINITSTRUCT data structure. Input.

Return Values

GS-SUCCESS   Initialized successfully.

GS-ERROR   Failed to initialize.

Prerequisites

GSINIT

Example

Initialize GeoStan for LACSLink.

***********  WORKING STORAGE VARIABLES ***********************
01 GSID            PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT       PIC S9(9) BINARY.
01 STRUCT-SIZE     PIC S9(9) BINARY.
01 W-HAVE-MESSAGE  PIC S9(9) BINARY.
01 W-ERROR-MSG     PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL  PIC X(256) VALUE LOW-VALUES.
 
COPY GSCONST.
 
*******  SAMPLE CODE TO INITIALIZE LACS/LINK *****************
**** PLACE AFTER CALL TO GSINIT    ***************************
MOVE GS-GEOSTAN-VERSION       TO GS-LIS-STRUCT-VERSION.
MOVE GS-LIS-COB-STRUCT-SIZE   TO STRUCT-SIZE.
 
CALL 'GSLACINR' USING GSID, GS-LACSLINK-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.
 
IF GSFUNSTAT = GS-SUCCESS
DISPLAY 'LACS INITIALIZED SUCCESSFULLY'
ELSE
DISPLAY '********************************'
DISPLAY 'LACS FAILED TO INITIALIZE'
DISPLAY 'GSFUNSTAT IS:', GSFUNSTAT
DISPLAY 'GSID IS:', GSID
DISPLAY 'GS-LACSLINK-INIT-STRUCT:', GS-DPV-INIT-STRUCT
DISPLAY 'STRUCT-SIZE IS:', STRUCT-SIZE
DISPLAY '********************************'
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
PERFORM UNTIL W-HAVE-MESSAGE IS EQUAL TO ZERO
CALL 'GSERRGTX' USING GSID, W-ERROR-MSG, W-ERROR-DETAIL, GSFUNSTAT
DISPLAY 'W-ERROR-MSG:', W-ERROR-MSG
DISPLAY 'W-ERROR-DETAIL:', W-ERROR-DETAIL
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
END-PERFORM

After you have initialized LACSLink and called GSSFIND for an address, you can then call GSDATGET and request any of the following output fields, which are included in the copy member GSCONST:

  • GS-LACS-FLAG

  • GS-LACSLINK-IND

  • GS-LACSLINK-RETCODE

GSSMIXED

Deprecated. Sets the casing of the returned information.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT               PIC 9(4) BINARY.
01 MIXED-CASE               PIC 9(4) BINARY.
*
CALL "GSSMIXED" USING GSID, MIXED-CASE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

MIXED-CASE   Sets the casing of the returned value; either 0 for upper case (default) or1 for mixed case. Input.

Return Values

Current setting for this option (the setting before the change).

Prerequisites

GSINIT

Notes

Casing affects the firm name, all address components, and City name. The USPS prefers upper case.

If you specify mixed case, generally only the first letter is set to upper case.

GSSMM

Deprecated. Controls the matching mode used by GSSFIND.

Syntax

01 GSID         PIC S9(9) BINARY.
01 MATCH-MODE         PIC 9(4) BINARY.
01 GSFUNSTAT         PIC 9(4) BINARY.
*
CALL "GSSMM" USING GSID, MATCH-MODE, GSFUNSTAT.

Arguments

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

MATCH-MODE   Variable value indicating match mode type. The following table contains the valid variables. Input.

GS-MODE-EXACT

Requires an exact name match. Generates the fewest number of possibles to search.

GS-MODE-CLOSE

Default. Requires a very close name match. Generates a moderate number of possibles to search

GS-MODE-RELAX

Requires a close name match. Generates the largest number of possibles to search.

GS-MODE-CASS

Requires a close name match. Generates the largest 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 street network file for standardization.

GSFUNSTAT   Contains the return value for the procedure. Output.

Return Values

Old match mode, or a -1 if the new match mode entered is invalid.

Prerequisites

GSINIT or GSCLEAR

Notes

GSSMM affects how GSDATSET performs. For this reason, call this procedure only immediately after GSINIT, or after a GSCLEAR. If you call this procedure after loading data with GSDATSET, the results are undefined.

GSSTRCEN

Deprecated. Used to enable street locator geocoding as an automatic geocoding fallback.

Syntax

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

Arguments

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

GSSTRCEN   Specifies whether or not to return a street segment geocode as an automatic geocoding fallback. Input.

n 0 = (default) Street locator disabled

n 1 = Return street segment geocode

GSFUNSTAT   Return value for the procedure. Output.

Return Values

Current setting for this option (the setting before the change).

Prerequisites

GSINIT

Notes

When this feature is enabled, if a street name is encountered while geocoding, and there is no matching address range, GeoStan will attempt to locate the street within the input ZIP Code or city if there is no input ZIP Code. If GeoStan is able to locate the street, it will return a geocode along the matched street segment rather than the geocode for the entered ZIP Code or ZIP + 4.

If a street number is entered, GeoStan will return the coordinates of the end point of the closest numeric street segment within the input ZIP Code. When there is no input ZIP Code, the closest numeric street segment of all the ZIP Codes within the input city will be returned.

If no street number is entered, the centroid of a matching street segment within the input ZIP Code will be returned. The centroid of a street segment for all the ZIP Codes within the input city will be returned when there is no input ZIP Code.

Match candidates may be returned. More information about the returned segment(s) can be obtained for either a single or a match candidate by calling GSMGet().

This option is not available in CASS mode.