COBOL procedures

GSCITYDG

Retrieves data located with GSCITYFF or GSCITYFN.

Syntax

01 GSID                             PIC S9(9) BINARY.
01 GSFUNSTAT                        PIC 9(9) BINARY.
01 GSOPTIONS                        PIC 9(9) BINARY.
01 OUTLEN                           PIC 9(9) BINARY.
01 CITY-NAME                       PIC X(USER LEN).
01 RECNUM                  PIC S9(9) BINARY.
*
CALL "GSCITYDG" USING GSID, RECNUM, GSOPTIONS, CITY-NAME, OUTLEN, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

GSOPTIONS   Symbolic constant for the data item to retrieve. The following table lists the valid variables. Input.

Variable

Size

Description

GS-CITY-CARRTSORT

(2)

•Y – Carrier Route Sort

•N – No Carrier Route Sort

GS-CITY-CITYDELV

(2)

•Y – Has city-delivery carrier routes

•N – Does not have city-delivery carrier routes

GS-CITY-CLASS

(2)

ZIP Classification Code.

GS-CITY-CTYSTKEY

(7)

6-character USPS City State Key that uniquely identifies a locale in the city/state file.

GS-CITY-FACILITY

(2)

Returns USPS City State Name Facility Code:

•A – Airport Mail Facility (AMF)

•B – Branch

•C – Community Post Office (CPO)

•D – Area Distribution Center (ADC)

•E – Sectional Center Facility (SCF)

•F – Delivery Distribution Center (DDC)

•G – General Mail Facility (GMF)

•K – Bulk Mail Center (BMC)

•M – Money Order Unit

•N – Non-Postal Community Name, Former Postal Facility, or Place Name

•P – Post Office

•S – Station

•U – Urbanization

GS-CITY-MAILIND

(2)

•1 – Can use City State Name as last line on mail piece

•0 – Cannot use City State Name as last line on main piece

GS-CITY-NAME

(30)

City name (may be an alternate name)

GS-CITY-PREFNAME

(30)

USPS preferred city name

GS-CITY-QCITY

(10)

City number, using the format ssffffccc, where s is the state number, f is the Finance number, and c is the city number

GS-CITY-UNIQUE

(2)

•Y – Unique ZIP Code (ZIP assigned to a single organization)

•Blank – Not applicable

GS-CITY-STATE

(3)

State Abbreviation

GS-CITY-ZIP

(6)

ZIP Code

CITY-NAME   Location to store the returned data. Output.

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

RECNUM   City record number, as returned by GSCITYFF or GSCITYFN. Input.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSCITYFF or GSCITYFN

Notes

The GSCITYDG procedure retrieves data about the city located with GSCITYFF or GSCITYFN. City information from the USPS City/State file.

GSCITYFF

Finds the first city matching partial name or valid ZIP Code.

Syntax

01 GSID                          PIC S9(9) BINARY.
01 GSFUNSTAT                PIC S9(9) BINARY.
01 STATE-NAME                     PIC X(USER LEN).
01 CITY-NAME                      PIC X(USER LEN).
*
CALL "GSCITYFF" USING GSID, STATE-NAME, CITY-NAME, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

STATE-NAME   Proper state abbreviation for the searched state, or " " for a ZIP Code search. Input.

CITY-NAME   City to search for (may be just a partial string), or a 3-digit or 5-digit ZIP Code. Input.

Return Values

Record number of the city located, or zero if GeoStan did not find any cities.

Prerequisites

GSCLEAR

Notes

This procedure retrieves the record number of the first city in a state that matches the city or ZIP Code search string. For example, if the entered state string is CA and the city string is S, Geostan finds the first city that begins with S in California. If the entered city string is 803 and the state string is null, GeoStan the first city in that sectional center. GeoStan does not return cities in any predefined order.

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.

GSCITYFN

Finds next city matching the partial name or valid ZIP Code.

Syntax

01 GSID               PIC S9(9) BINARY.
01 LSTATUS            PIC S9(9) BINARY.
*
CALL "GSCITYFN" USING GSID, LSTATUS.

Arguments

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

LSTATUS   Return code. Output.

Return Values

Record number of the city located, or zero if GeoStan did not find any cities.

Prerequisites

GSCITYFF or GSCLEAR

Notes

Call this procedure after GSCITYFF.

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.

GSCLEAR

Clears the data buffer in the internal data structures.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Notes

Before each find function, call GSCLEAR to reset the buffers to null. If you do not reset the buffers, you may receive incorrect results with information from a previous find. This call clears only address element and locational information about the previously processed address and does not affect distance or centroid match type.

GSDATGET

Returns data for all address and matched elements from GeoStan.

Syntax

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

Arguments

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

GSOPTIONS   Flag indicating whether to retrieve original or processed data. Input.

To retrieve parsed address components, set GSOPTIONS to GS-INPUT. To retrieve matched address information from the parsed input address and the GeoStan database, set GSOPTIONS to GS-OUTPUT.

If the input address does not match, setting GSOPTIONS to GS-OUTPUT returns the address exactly as entered, except for the last line information, which returns only the parsed last line components.

The parsed last line components correspond to the following variables:

GS-LASTLINE

GS-ZIP

GS-ZIP9

GS-CITY

GS-ZIP4

GS-ZIP10

GS-STATE

 

 

If there is extra data on the input last line (GS-LASTLINE), this data is not retrievable. For example, in the last line "BOULDER CO 80301 US OF A", "US OF A" is not retrievable from any GSDATGET() procedure.

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

GSSWITCH   Symbolic constant for the data item to retrieve. Input.

GSFUNSTAT   Return value for the procedure. Output.

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

OUTLEN   Maximum length of data for GeoStan to return. The COBOL copy member "GEOSTAN" lists as constants the recommended buffer size for each item. These sizes are the maximum lengths required to get the full output string. You can allocate a buffer that is smaller or larger than these values. However, if bufLen is shorter than the returned data, GeoStan truncates the data and does not generate an error. Input.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSSFINDWP

Notes

This procedure retrieves data elements from internal GeoStan buffers for either the original (input) or matched (output) data elements. To retrieve original data, set GSOPTIONS to GS-INPUT. To retrieve matched data, set GSOPTIONS to GS-OUTPUT.

GSDATSET

Passes data for all address elements to GeoStan.

Syntax

01 GSID                           PIC S9(9) BINARY.
01 GSFUNSTAT                      PIC S9(9) BINARY.
01 GSOPTIONS                      PIC 9(9) BINARY.
01 VALUE                  PIC X(LEN).
*
CALL "GSDATSET" USING GSID, GSOPTIONS, VALUE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

GSOPTIONS   Symbolic constant for the data item to load. See Variables for storing and retrieving data" for a list of valid variables. Input.

VALUE   String pointer containing the data to be loaded. Input.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSINITWP

Notes

This procedure loads data elements into internal GeoStan buffers. When loading address information as a complete address or last line, GeoStan parses the data into fields. For example, if you entered a last line of "Boulder, CO 80301-1234", GeoStan parses the data and sets the city, state, ZIP, and ZIP + 4 fields. You can retrieve parsed data using GSDATGET and requesting the INPUT to these fields.

If you are passing both an address line and a last line or ZIP Code, be sure to enter the last line or ZIP Code first to ensure the greatest accuracy in address standardization.

If you are passing both the address information and the last line information as one input line, enter the address information first.

Using the appropriate  parameters defined in the COBOL copy member "GEOSTAN", you can pass singleline addresses, two-line addresses, or multiline addresses of up to six lines. For more information, see Appendix B: Extracting Data from GSD Files.

Do not call GSSMM after a call to GSDATSET. If you need to change the match mode in mid-process, you must re-enter the data for the current address with GSDATSET.

GSDBMETA

Retrieves information about each database file.

Syntax

01 GSID PIC S9(9) BINARY.
01 GSFUNSTAT PIC S9(9) BINARY.
01 DB-NUMBER PIC S9(9) BINARY.
01 ITEM-CODE PIC S9(9) BINARY.
01 STRING-BUFFER PIC X(USER LEN).
01 BUFFER-LENGTH PIC S9(9) BINARY.
*
BUFFER-LENGTH = LENGTH OF STRING-BUFFER.
CALL "GSDBMETA" USING GSID, ITEM-CODE, DB-NUMBER, STRING-BUFFER, BUFFER-LENGTH,   GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

ITEM-CODE   Code for data item requested.   Input.

DB-NUMBER   Database file number.   Input.

STRING-BUFFER   Return value for requested data item. Output.

BUFFER-LENGTH   Maximum size of returned value string.  Input.

The following named code values are defined in the copy member "GEOSTAN" for this function:

GS-STATUS-DATATYPE-NUM

Source data type number.

GS-STATUS-DATATYPE-STR

Source data type descriptive text.

GS-STATUS-DATUM-NUM

Coordinate system code.

GS-STATUS-DATUM-STR

Coordinate system name (Datum)

GS-STATUS-FILE-CHKSUM-NUM

File Header checksum.

GS-STATUS-RDI-FILE-ALL

If true, USPS RDI data loaded successfully.

GS-STATUS-RECORDS-REMAINING

Metered retrievals remaining (for metered usage license only).

GS-STATUS-GEO-RECORD-TOTAL

Metered retrievals available by license (for metered usage license only).

GS-STATUS-DAYS-REMAINING

Usage days remaining (for temporary license only).

GS-STATUS-GEO-PRECISION

Coordinate precision of data source - number of digits.

GS-STATUS-DB-COPYRIGHT

Copyright declarations for data source.

GS-STATUS-DB-COUNTRY

Country name for data source.

GS-STATUS-DB-VERSION

Database version number.

GS-STATUS-DB-FILE-PATH

File name.

Return Values

Returns.

Prerequisites

GSINITWP

Notes

The value in the string buffer is space-padded to the length of the buffer and has no terminator. If the buffer length is shorter than the available value, the returned value will be truncated. The maximum size of any string returned is 255 characters.

GSDPVGCS

Obtains the complete DPV statistics since the application initialized DPV.
Note: If singleline address input is used, the output from GSDPVGCS will be incorrect.

Syntax

01 GSID             PIC S9(9) BINARY.
01 GS-LACS-COMPLETE-STATS      
01 RETURN-CODE            PIC 9(9) BINARY.
CALL "GSDPVGCS" USING GSID, GS-DPV-COMPLETE-STATS, GS-DCS-SIZE, RETURN-CODE.

Arguments

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

GS-LACS-COMPLETE-STATS    Structure containing the following DPV statistics since the application initialized DPV:

GS-DCS-NCMRA-IN-ERROR    Number of records with a CMRA unconfirmed. Output.

GS-DCS-NCMRA-VALID    Number of records with a CMRA confirmed. Output.

GS-DCS-NDPV-IN-ERROR    Number of records not confirmed by DPV. Output.

GS-DCS-NDPV-NO-STAT-FOUND    Not Applicable for this release. Output.

GS-DCS-NDPV-SEED-HITS    Number of DPV false positive matches. Output.

GS-DCS-NDPV-TYPES-ERROR    Number of records with a valid primary range, but the secondary range is not confirmed. Output.

GS-DCS-NDPV-TYPEY-ERROR    Number of records fully confirmed by DPV. Output.

GS-DCS-NDPV-ZIPS-ON-FILE    Number of distinct ZIP Codes in file. Output.

GS-DCS-NFIRM-CMRA-PRESENTED    Number of USPS Firm records with PMB presented. Output.

GS-DCS-NFIRM-CMRA-VALID    Number of USPS Firm records CMRA confirmed with or without PMB. Output.

GS-DCS-NFIRM-PRIME-FAIL    Number of USPS Firm records without a confirmed primary number. Output.

GS-DCS-NFIRM-SECONDARY-FAIL    Number of USPS Firm records failed to confirm secondary number. Output.

GS-DCS-NFIRM-VALID    Number of confirmed USPS Firm records. Output.

GS-DCS-NGEN-DEL-VALID    Number of confirmed USPS General Delivery records. Output.

GS-DCS-NHR-CMRA-PRESENTED    Number of USPS Highrise records with PMB presented. Output.

GS-DCS-NHR-CMRA-VALID    Number of USPS Highrise with confirmed CMRA records with or without PMB. Output.

GS-DCS-NHR-PRIME-FAIL    Number of USPS Highrise records failed to confirm primary number. Output.

GS-DCS-NHR-SECONDARY-FAIL    Number of USPS Highrise records failed to confirm secondary number. Output.

GS-DCS-NHR-VALID    Number of confirmed USPS Highrise records. Output.

GS-DCS-NPO-BOX-FAIL    Number of USPS PO Box records failed to confirm primary number. Output.

GS-DCS-NPO-BOX-VALID    Number of confirmed USPS PO Box records. Output.

GS-DCS-NRR-CMRA-PRESENTED    Number of USPS Rural Route records with PMB presented to the DPV data. Output.

GS-DCS-NRR-CMRA-VALID    Number of USPS Rural Route records CMRA confirmed with or without PMB. Output.

GS-DCS-NRR-HC-PRIME-FAIL    Number of USPS Rural Route records failed to confirm primary number. Output.

GS-DCS-NRR-HC-VALID    Number of USPS Rural Route records confirmed. Output

GS-DCS-NST-CMRA-PRESENTED    Number of USPS Street records with PMB presented. Output.

GS-DCS-NST-CMRA-VALID    Number of USPS Street records CMRA confirmed with or without PMB. Output.

GS-DCS-NSTREET-PRIME-FAIL    Number of USPS Street records failed to confirm primary number. Output.

GS-DCS-NSTREET-SECONDARY-FAIL    Number of USPS Street records fail to confirm secondary number. Output.

GS-DCS-NTOTAL-DPV-PROCESSED    Number of records processed through DPV. Output.

GS-DCS-NTOTAL-DPV-WITH-ZIP4    Number of records with ZIP + 4 processed through DPV. Output.

GS-DCS-FOOTNOTE-AA    Number of records with DPV footnote value AA. Output.

GS-DCS-FOOTNOTE-A1    Number of records with DPV footnote value A1. Output.

GS-DCS-FOOTNOTE-BB    Number of records with DPV footnote value BB. Output.

GS-DCS-FOOTNOTE-CC    Number of records with DPV footnote value CC. Output.

GS-DCS-FOOTNOTE-F1    Number of records with DPV footnote value F1. Output.

GS-DCS-FOOTNOTE-G1    Number of records with DPV footnote value G1. Output.

GS-DCS-FOOTNOTE-M1    Number of records with DPV footnote value M1. Output.

GS-DCS-FOOTNOTE-M3    Number of records with DPV footnote value M3. Output.

GS-DCS-FOOTNOTE-N1    Number of records with DPV footnote value N1. Output.

GS-DCS-FOOTNOTE-P1    Number of records with DPV footnote value P1. Output.

GS-DCS-FOOTNOTE-P3    Number of records with DPV footnote value P3. Output.

GS-DCS-FOOTNOTE-RR    Number of records with DPV footnote value RR. Output.

GS-DCS-FOOTNOTE-R1    Number of records with DPV footnote value R1. Output.

GS-DCS-FOOTNOTE-U1    Number of records with DPV footnote value U1. Output.

RETURN-CODE    Size of the GSDPVGCS data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR    Call GSERRGTX for more information

GS-WARNING   Call GSERRGTX for more information

Prerequisites

GSINITWP

GSDPVGFD

Retrieves the detail record for a DPV false positive report.

Syntax

01 GSID                PIC S9(9) BINARY.
01 GS-FALSE-POS-DETAIL-DATA
01 RETURN-CODE               PIC 9(9) BINARY.
CALL "GSDPVGFD" USING GSID, GS-FALSE-POS-DEFAILT-DATA, GS-FPDD-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-DETAIL-DATA    Retrieves the DPV detail record for a false positive address match using the data passed in GSDPVDFD. The data members are details provided by GeoStan for the false positive report. This structure contains the following:

GS-FPPD-ADDRESS-SECONDARY-ABBRV    Unit type (APT, SUITE, LOT).Output.

GS-FPPD-ADDRESS-SECONDARY-NUM    Unit number.Output.

GS-FPPD-MATCHED-PLUS4    ZIP Code extension. Output.

GS-FPPD-MATCHED-ZIP-CODE    ZIP Code.Output.

GS-FPPD-POST-DIRECTIONAL    Street name postdirectional (N, S, E, W). Output.

GS-FPPD-PRIMARY-NUMBER    House number.Output.

GS-FPPD-STREET-NAME    Street name. Output.

GS-FPPD-STREET-PREDIR    Street name predirectional (N, S, E, W). Output.

GS-FPPD-SUFFIX-ABBREVIATION    Street type (AVE, ST, RD). Output.

FILLER    Reserved for future implementation. Output.

RETURN-CODE   Size of the GsFalsePosDetailData data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information

GS-WARNING   Call GSERRGTX for more information

Prerequisites

GSDPVINR

GSDPVGFH

Retrieves DPV statistics for the header record for a DPV false positive report.
Note: If singleline address input is used, the output from GSDPVGFH will be incorrect.

Syntax

01 GSID                   PIC S9(9) BINARY.
GS-FALSE-POS-HEADER-DATA
01 RETURN-CODE                  PIC 9(9) BINARY.
CALL "GSDPVGFH" USING GSID, GS-FALSE-POS-HEADER-DATA, GS-FPHD-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-HEADER-DATA    Retrieves DPV statistics from the header record for false positive address matches using the data passed in GSDPVGFD. The output data members are statistics for the false positive reports. The input data members include information to correctly complete the false positive report for the USPS. This structure contains the following:

GS-FPHD-MAILERS-ADDRESS-LINE    Address of the mailer. Input.

GS-FPHD-MAILERS-CITY-NAME    City of the mailer. Input.

GS-FPHD-MAILERS-COMPANY-NAME    Name of the mailer. Input.

GS-FPHD-MAILERS-STATE-NAME    State of the mailer. Input.

GS-FPHD-MAILERS9-DIGITZIP    ZIP Code of the mailer. Input.

GS-FPHD-NUMBER-FALSE-POS    Number of found DPV false positive matches. Output.

GS-FPHD-NUMBER-ZIP-ON-FILE    Number of distinct ZIP Codes processed through DPV. Output.

GS-FPHD-TOTAL-MATCHED    Number of records matched with DPV data. Output.

GS-FPHD-TOTAL-PROCESSED    Number of records processed through DPV. Output.

GS-FPHD-TOTAL-ZIP4-MATCHED    Number of records that have matched with ZIP + 4. Output.

RETURN-CODE    Size of the GSDPVGFD data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information

GS-WARNING   Call GSERRGTX for more information

Prerequisites

GSINITWPwith the appropriate DPV initialization properties set.

GSERRGET

Retrieves current error information.

Syntax

01 GSID                  PIC S9(9) BINARY.
01 GSFUNSTAT                      PIC S9(9) BINARY.
01 MESSAGE-STRING                   PIC X(256).
01 DETAIL-STRING                   PIC X(256).
*
CALL "GSERRGET" USING GSID, MESSAGE-STRING, DETAIL-STRING, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

MESSAGE-STRING    Basic explanation for the error; up to 256 bytes in length. Output.

DETAIL-STRING    Particulars of an error, such as filename; up to 256 bytes in length. Output.

Note: Always set buffers for MESSAGE-STRING and DETAIL-STRING to 256 bytes or larger.

Return Values

Error number of the most recent GeoStan error.

-1

No error.

0 through 99

Indicates the actual DOS error values.

100

Unclassified error.

101

Unknown error.

102

Invalid file signature.

103

Table overflow.

104

Insufficient memory.

105

File not found.

106

Invalid argument to a procedure.

107

File is out of date.

108

Invalid license filename, path, or incorrect password.

109

Invalid GsFind call - cannot match an address and a geocode in the same GsFind call.

110

Could not determine centerline.

111

Invalid checksum on file contents.

112

System exception (e.g. access violation).

Alternates

GSERRGTX

GSERRGTX

Retrieves informational, error, and fatal warning messages for the current thread.

Syntax

01 GSID                         PIC S9(9) BINARY.
01 ERROR-MESSAGE                         PIC X(256).
01    DETAILS                      PIC X(256).
01    GSFUNSTAT                     PIC S9(9) BINARY.
 
CALL "GSERRGTX" USING GSID, ERROR-MESSAGE, DETAILS, GSFUNSTAT.

Arguments

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

ERROR-MESSAGE    GeoStan error code and descriptive text. Output.

DETAILS   Descriptive message, such as the file name associated with the error. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return values

Next GeoStan error detected in the current thread. Upon return, error messages contain a brief description and additional text, such as the name of the file or directory associated with the error.

Note: Not all errors are fatal. For example, if GeoStan finds an inappropriate GSI file, it reports the error but continues executing.

Prerequisites

GSINITWP and GSERRHAS

GSERRHAS

Indicates if any errors occurred or any information messages are available in the current thread.

Syntax

01 GSID                      PIC S9(9) BINARY.
01 MOREERRORS                      PIC S9(9) BINARY.
 
CALL "GSERRHAS" USING GSID, MOREERRORS.

Arguments

GSID   ID returned by GSINITWP if initialization completed, or set to NULL if initialization failed and GSINITWP returned NULL. Input.

MOREERRORS   Zero if there are no more error messages to retrieve (via GSERRGTX), and non-zero if there are additional messages. Output.

Return Values

non-zero value    Errors occurred or GeoStan generated informational messages

zero    No errors or informational messages are pending.

Prerequisites

   GSINITWP

GSFCASSH

Writes a CASS 3553 report to the header buffer argument.

Syntax

01    GSID                  PIC S9(9).      
01    GSEXTENDCASSDATA
01    HEADER-BUFFER                  PIC X(USER LEN).
01    DATA-SIZE                  PIC S9(9) BINARY.
01    BUFSIZE                  PIC S9(9) BINARY.
01    GSFUNSTAT                  PIC S9(9) BINARY.
 
CALL "GSFCASSH" USING GSID, GSEXTENDCASSDATA, DATA-SIZE, HEADER-BUFFER, BUFSIZE, GSFUNSTAT.

Arguments

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

GSEXTENDCASSDATA    Pointer to the CASSS report data structure. The following table contains information about the structure. Input.

05

GS-ECD-STRUC-TVERSION

PIC S9(9) BINARY.

05

GS-ECD-NRECS   

PIC S9(9) BINARY.

05

GS-ECD-NZIP4   

PIC S9(9) BINARY.

05

GS-ECD NZIP

PIC S9(9) BINARY.

05

GS-ECD-NCARRT

PIC S9(9) BINARY.

05

GS-ECD-NDPBC

PIC S9(9) BINARY.

05

GS-ECD-LISTNAME

PIC X(20).

05

GS-ECD-VERSION   

PIC X(12).

05

GS-ECD-CERTIFICATION-DATE   

PIC X(24).

05

GS-ECD-SEARCH-PATH   

PIC X(256).

05

GS-ECD-TEMPLATE-NAME   

PIC X(256).

05

GS-ECD-NZ4CHANGED

PIC 9(9) BINARY.

05

GS-ECD-NLOT   

PIC 9(9) BINARY.

05

GS-ECD-Z4CHANGE-VERSION   

PIC X(12).

05

GS-ECD-LOT-VERSION   

PIC X(12).

05

GS-ECD-NHIGHRISE-DEFAULT   

PIC S9(9) BINARY.

05

GS-ECD-NHIGHRISE-EXACT   

PIC S9(9) BINARY.

05

GS-ECD-NRURALROUTE-DEFAULT   

PIC S9(9) BINARY.

05

GS-ECD-NRURALROUTE-EXACT   

PIC S9(9) BINARY.

05

GS-ECD-NLACS   

PIC S9(9) BINARY.

05

GS-ECD-Z4-COMPANY-NAME   

PIC X(40).

05

GS-ECD-DPC-COMPANY-NAME   

PIC X(40).

05

GS-ECD-Z4-CONFIG   

PIC X(3).

05

GS-ECD-DPC-CONFIG

PIC X(3).

05

GS-ECD-Z4-SOFTWARE-NAME   

PIC X(30).

05

GS-ECD-DPC-SOFTWARE-NAME   

PIC X(30).

05

GS-ECD-LIST-PROCESSOR-NAME   

PIC X(25).

05

FILLER   

PIC X(3).

05

GS-ECD-ZIP4-DATABASE-DATE   

PIC S9(9) BINARY.

05

GS-ECD-LOT-DATABASE-DATE   

PIC S9(9) BINARY.

05

GS-ECD-EWS-DENIAL   

PIC S9(9) BINARY.

DATA-SIZE   Size of the CASS report data structure. Input.

HEADER-BUFFER    Buffer containing the CASS header line from the Stage file. Input, Output.

BUFSIZE   Length of the header buffer. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

GS-WARNING

Prerequisites

GSINITWP

Notes

When you specify a version number for either version, GS-ECD-LOT-VERSION or GS-ECD-LOT-VERSION, GeoStan updates the corresponding fields in the header buffer similar to GSWECASS. For example, entering a version number for GS-ECD-LOT-VERSION prompts GeoStan to fill the following fields in CASS355.frm:

  • Section "B. List", Item "2b": Data List Processed Z4Change

  • Section "B. List", Item "3b": Data of Database Product used Z4Change.

  • Section "C. Output", Item "1b": Total coded Z4Change Processed.

To develop CASS certified application in GeoStan, you must have the correct license agreement with Precisely. You must also obtain CASS certification from the USPS for your application. Using GeoStan does not make an application CASS certified. For information on becoming CASS certified, see Appendix E: CASS certification overview.

GSFDFPD

Formats a DPV false positive detail record from GSDPVGFD.

Syntax

01 GSID                PIC S9(9) BINARY.
01 GS-FALSE-POS-DETAIL-DATA      
01 RETURN-CODE                PIC 9(9) BINARY.
01 HEADER                PIC X(len)
01 HEADER-SIZE                PIC 9(9) BINARY VALUE len.
 
CALL "GSFDFPD" USING GSID, GS-FALSE-POS-DETAIL-DATA, GS-FPHD-SIZE, HEADER, HEADER-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-DETAIL-DATA    Pointer to the DPV report data structure. This value is completed by GSDPVGFD. Input.

RETURN-CODE   Size of the DPV report data structure. Input.

HEADER   Buffer containing the DPV false positive detail record after GSFDPD successfully completes. When the application writes the false positive report, it writes this buffer to the last line of the file. Output.

HEADER-SIZE   Length of the detail buffer. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSDPVGFD

GSFDFPH

Formats a DPV false positive header record with data from GSDPVGFD.
Note: If singleline address input is used, the output from GSFDFPH will be incorrect.

Syntax

01 GSID       PIC S9(9) BINARY.
01 GS-FALSE-POS-HEADER-DATA
01 RETURN-CODE       PIC 9(9) BINARY.
01 HEADER       PIC X(len).
01 HEADER-SIZE       PIC 9(9) BINARY VALUE len.
 
CALL "GSFDFPH" USING GSID, GS-FALSE-POS-HEADER-DATA, GS-FPHD-SIZE, HEADER, HEADER-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-HEADER-DATA    Pointer to the DPV report data structure. This value is completed by GSDPVGFH. Input.

RETURN-CODE   Size of the DPV report data structure. Input.

HEADER   Buffer containing the DPV false positive header after GSFDFPH successfully completes. When the application writes the false positive report, it writes this buffer to the first line of the file. Output.

HEADER-SIZE   Length of the header buffer. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSDPVINR
GSDPVGFH

GSFFRANG

Finds the first range object that meets the search criteria.

Syntax

01    GSID                  PIC S9(9) BINARY.
01    RANGE-HANDLE                  PIC S9(9) BINARY.
01    GSFUNSTAT                  PIC S9(9) BINARY.
*
CALL "GSFFRANG" USING GSID, RANGE-HANDLE, GSFUNSTAT.

Arguments

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

RANGE-HANDLE   Pointer to a range handle. Returns a valid handle if GeoStan finds a range. Input, Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

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

GS-NOT-FOUND    Did not find a match.

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

Prerequisites

GSINITWP and GSCLEAR

Notes

You must call GSFFSEG before calling GSFFRANG.

GSFFSEG

Finds the first segment object that meets the search criteria.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 SEGMENT-HANDLE    PIC S9(9) BINARY.
*
CALL "GSFFSEG" USING GSID, SEGMENT-HANDLE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

SEGMENT-HANDLE    Pointer to a street/segment handle. Returns a valid handle if GeoStan finds a segment. Input, Output.

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-ERROR    An error occurred; use GSERRGET and GSERRGTX to retrieve more information.

Prerequisites

GSINITWP and GSCLEAR

Notes

This procedure finds the first street in the current search area that meets the name criteria, and also sets the area and criteria for subsequent segment and range searches.

If you are using GSFFSEG 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.

GSFFSEG and GSFNRANG procedures work together to allow you to access to the entire address directory database.

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

GSFFST

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 Appendix B: Extracting Data from GSD Files for more information on the Find First and Find Next procedures.

GSFFSTAT

Finds the USPS state name abbreviation.

Syntax

01 GSID                  PIC S9(9) BINARY.
01 GSFUNSTAT                  PIC 9(9) BINARY.
01 OUTLEN                   PIC 9(9) BINARY.
01 STATE-FOUND                   PIC X(USER LEN).
01 STATE-PATTERN                   PIC X(USER LEN).
*
CALL "GSFFSTAT" USING GSID, STATE-PATTERN, STATE-FOUND, OUTLEN, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

OUTLEN   Maximum length of data returned in STATE-FOUND, including NULL. Input.

STATE-FOUND   Proper state abbreviation for located state. Output.

STATE-PATTERN    Search string for state. Input.

Can be any of the following items:

n Five-digit ZIP Code.

n First three digits of a ZIP Code known as the Sectional Center Facility (SCF).

n Various state abbreviations and spellings. For example, for New Hampshire, it accepts: N HAMP, N HAMPSHIRE, NEW HAMPSHIRE, NEWHAMPSHIRE, NH, and NHAMPSHIRE.

Return Value

GS-ERROR

GS-SUCCESS

GS-NOT-FOUND

Prerequisites

GSINITWP or GSCLEAR

Notes

This procedure returns the proper abbreviation for the requested state. You can request states either by ZIP Code, full state name, or an alternate abbreviation.

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.

GSFGF

Finds the first geographic information record with partial matching to input names.

Syntax

01 GSID PIC S9(9) BINARY.
01 GSFUNSTAT PIC S9(9) BINARY.
*
MOVE SPACES TO GS-GEOGRAPHIC-INFO.
MOVE <a City Name> TO GS-INPUT-CITY.
MOVE <a County Name> TO GS-INPUT-COUNTY.
MOVE <a State Name/Abbreviation> TO GS-INPUT-STATE.
 
CALL "GSFGF" USING GSID, GS-GEOGRAPHIC-INFO, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

GS-INPUT-CITY    City Name (may be a partial string). Input.

GS-INPUT-COUNTY    County Name (may be a partial string). Optional. Input.

GS-INPU-STATE    Proper state abbreviation or name for the searched state. Input.

Return Values

First Geographic Information Record which has a partial match to the input.

"GSFUNSTAT" contains a value of "GS-SUCCESS" if there are one or more matching records.

The following named items are defined in module the COBOL copy member "GEOSTAN" for this function:

GS-OUTPUT-CITY

Full City name.

GS-OUTPUT-COUNTY

County name.

GS-OUTPUT-STATE

State FIPS abbreviation.

GS-OUTPUT-LAT

Latitude.

GS-OUTPUT-LONG

Longitude.

GS-OUTPUT-RANK

Metropolitan Area Economic and Population Rank.

GS-OUTPUT-RESULT-CODE

GeoStan Match result code.

GS-OUTPUT-LOCATION-CODE

Geostan Location code.

GS-CLOSE-MATCH-FLAG

Indicates close name match.

Prerequisites

GSINITWP

Notes

This procedure retrieves the first Geographic information record which matches the input city, county, or state names. The match logic may qualify more than one response. Use calls to "GSFGN" to retrieve the additional responses.

The COBOL copy member "GEOSTAN" includes the record "GS-GEOGRAPHIC-INFO" which has the correct format for this function.

Input values may be zero-byte terminated strings or fixed-length with space padding. The returned values are fixed-length with space padding. The optional field "GS-INPUT-COUNTY" should be filled with spaces if it is not used.

GSFGFX

Finds the first city, county, and or state centroid match from the set of possible matches found.

Syntax

01 GS-GEOGRAPHIC-INFO-EX.
  05 GS-INPUT-CITY                     PIC X(39).
  05 GS-INPUT-COUNTY                     PIC X(39).
  05 GS-INPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-CITY                     PIC X(39).
  05 GS-OUTPUT-COUNTY                     PIC X(39).
  05 GS-OUTPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-LAT                     PIC X(11).
  05 GS-OUTPUT-LONG                     PIC X(12).
  05 GS-OUTPUT-RANK                     PIC X(2).
  05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
  05 GS-OUTPUT-LOCATION-CODE                     PIC X(5).
  05 GS-CLOSE-MATCH-FLAG                     PIC X.
  05 GS-INPUT-GEO-LIB-VER-EX                     PIC 9(9) BINARY.
  05 GS-OUTPUT-FIPS-CODE                     PIC X(6).
 
*
CALL "GSFGFX" USING NAME,.

Arguments

GS-INPUT-CITY    City Name (may be a partial string). Input.

GS-INPUT-COUNTY    County Name (may be a partial string). Optional. Input.

GS-INPUT-STATE    Proper state abbreviation or name for the searched state. Input.

GS-OUTPUT-CITY    Output city. Output.

GS-OUTPUT-COUNTY    Output county. Output.

GS-OUTPUT-STATE    Output state. Output.

GS-OUTPUT-LAT    Returned latitude of the geographic centroid. Output.

GS-OUTPUT-LONG    Returned longitude of the geographic centroid. Output.

GS-OUTPUT-RANK    Returned geographic rank of the city for city centroid. Output.

GS-OUTPUT-RESULT-CODE    Result code equivalent (G3 - city centroid, G2 - country centroid, G1 – state centroid). Output.

GS-OUTPUT-LOCATION-CODE    Location code equivalent (GM - city, GC - county, GS - state). Output.

GS-OUTPUT-GEO-LIB-VER-EX    GeoStan version. Input.

GS-OUTPUT-CLOSE    True indicates a close match. Output.

GS-OUTPUT-FIPS-CODE    FIPS Code. Output.

Return Values

GS-SUCCESS
GS-ERROR
GS-NOT-FOUND

Prerequisites

GSINITWP

Notes

It is recommended that the user first use the Last-line lookup functions to standardize the city, county and state names. This function only performs minimal fuzzy matching on the input city and county names. The location code returned by this function is to provide users with a location code equivalent and is not retrievable using GsDataGet. It is merely provided to offer a consistent label for the type of address match that is returned and will only consist of one of the three Geographic location codes (GM – City, GC – County and GS – State).

Example

Use the following parameter area defined in the COBOL copy member named GEOSTAN filling in the fields with names beginning with GS-INPUT.

01 GS-GEOGRAPHIC-INFO-EX.
  05 GS-INPUT-CITY                     PIC X(39).
  05 GS-INPUT-COUNTY                     PIC X(39).
  05 GS-INPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-CITY                     PIC X(39).
  05 GS-OUTPUT-COUNTY                     PIC X(39).
  05 GS-OUTPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-LAT                     PIC X(11).
  05 GS-OUTPUT-LONG                     PIC X(12).
  05 GS-OUTPUT-RANK                     PIC X(2).
  05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
  05 GS-OUTPUT-LOCATION-CODE                     PIC X(5).
  05 GS-CLOSE-MATCH-FLAG                     PIC X.
  05 GS-INPUT-GEO-LIB-VER-EX                     PIC 9(9) BINARY.
  05 GS-OUTPUT-FIPS-CODE                     PIC X(6).
 

For a COBOL coding example, see the example for GSFGF. The call is the same except that there are more output fields returned with GSFGFX.Finds the first geographic information record with partial matching to input names.

GSFGN

Finds the next geographic information record with partial matching to input names.

Syntax

01 GSID PIC S9(9) BINARY.
01 GSFUNSTAT PIC S9(9) BINARY.
*
CALL "GSFGN" USING GSID, GS-GEOGRAPHIC-INFO, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

Next Geographic Information Record which has a partial match to the input.

"GSFUNSTAT" contains a value of "GS-SUCCESS" if there are one or more matching records.

See GSFGF for the remainder of the output fields.

Prerequisites

GSINITWP
GSFGF (Previous call with return status equal "GS-SUCCESS")

Notes

This procedure retrieves the next Geographic information record which matches the input city, county, or state names.   A previous call to "GSFGF" is required, with a returned status of "GS-SUCCESS".

The COBOL copy member "GEOSTAN" includes the record "GS-GEOGRAPHIC-INFO" which has the correct format for this function.

Input values may be zero-byte terminated strings or fixed-length with space padding. The returned values are fixed-length with space padding. The optional field "GS-INPUT-COUNTY" should be filled with spaces if it is not used.

GSFGNX

finds the next city, county, and or state centroid match from the set of possible matches found.

Syntax

01 GS-GEOGRAPHIC-INFO-EX.
  05 GS-INPUT-CITY                     PIC X(39).
  05 GS-INPUT-COUNTY                     PIC X(39).
  05 GS-INPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-CITY                     PIC X(39).
  05 GS-OUTPUT-COUNTY                     PIC X(39).
  05 GS-OUTPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-LAT                     PIC X(11).
  05 GS-OUTPUT-LONG                     PIC X(12).
  05 GS-OUTPUT-RANK                     PIC X(2).
  05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
  05 GS-OUTPUT-LOCATION-CODE                     PIC X(5).
  05 GS-CLOSE-MATCH-FLAG                     PIC X.
  05 GS-INPUT-GEO-LIB-VER-EX                     PIC 9(9) BINARY.
  05 GS-OUTPUT-FIPS-CODE                     PIC X(6).
 
*
CALL "GSFGFX" USING NAME,.

Arguments

GS-INPUT-CITY    City Name (may be a partial string). Input.

GS-INPUT-COUNTY    County Name (may be a partial string). Optional. Input.

GS-INPUT-STATE    Proper state abbreviation or name for the searched state. Input.

GS-OUTPUT-CITY    Output city. Output.

GS-OUTPUT-COUNTY    Output county. Output.

GS-OUTPUT-STATE    Output state. Output.

GS-OUTPUT-LAT    Returned latitude of the geographic centroid. Output.

GS-OUTPUT-LONG    Returned longitude of the geographic centroid. Output.

GS-OUTPUT-RANK    Returned geographic rank of the city for city centroid. Output.

GS-OUTPUT-RESULT-CODE    Result code equivalent (G3 - city centroid, G2 - country centroid, G1 – state centroid). Output.

GS-OUTPUT-LOCATION-CODE    Location code equivalent (GM - city, GC - county, GS - state). Output.

GS-OUTPUT-GEO-LIB-VER-EX    GeoStan version. Input.

GS-OUTPUT-CLOSE    True indicates a close match. Output.

GS-OUTPUT-FIPS-CODE    FIPS Code. Output.

Return Values

GS-SUCCESS
GS-ERROR
GS-NOT-FOUND

Prerequisites

GSINITWP

Notes

It is recommended that the user first use the Last-line lookup functions to standardize the city, county and state names. This function only performs minimal fuzzy matching on the input city and county names. The location code returned by this function is to provide users with a location code equivalent and is not retrievable using GsDataGet. It is merely provided to offer a consistent label for the type of address match that is returned and will only consist of one of the three Geographic location codes (GM – City, GC – County and GS – State).

Example

Use the following parameter area defined in the COBOL copy member named GEOSTAN filling in the fields with names beginning with GS-INPUT.

01 GS-GEOGRAPHIC-INFO-EX.
  05 GS-INPUT-CITY                     PIC X(39).
  05 GS-INPUT-COUNTY                     PIC X(39).
  05 GS-INPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-CITY                     PIC X(39).
  05 GS-OUTPUT-COUNTY                     PIC X(39).
  05 GS-OUTPUT-STATE                     PIC X(20).
  05 GS-OUTPUT-LAT                     PIC X(11).
  05 GS-OUTPUT-LONG                     PIC X(12).
  05 GS-OUTPUT-RANK                     PIC X(2).
  05 GS-OUTPUT-RESULT-CODE                     PIC X(11).
  05 GS-OUTPUT-LOCATION-CODE                     PIC X(5).
  05 GS-CLOSE-MATCH-FLAG                     PIC X.
  05 GS-INPUT-GEO-LIB-VER-EX                     PIC 9(9) BINARY.
  05 GS-OUTPUT-FIPS-CODE                     PIC X(6).
 

For a COBOL coding example, see the example for GSFGF.The call is the same except that there are more output fields returned with GSFGFX. Finds the first geographic information record with partial matching to input names.

GSGETNDB

Returns the number of loaded databases.

Syntax

01 GSID PIC S9(9) BINARY.
01 DBCOUNT PIC S9(9) BINARY.
*
CALL "GSGETNDB" USING GSID, DBCOUNT.

Arguments

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

DBCOUNT   Number of GeoStan databases loaded. Output.

Return Values

Count of GeoStan database files loaded, or zero if GeoStan did not load any databases.

Prerequisites

GSINITWP

GSFINDWP

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

GSPLSTCRandGSPSET* 

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.   

GSFNRANG

Finds the next range object that meets the search criteria.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 RANGE-HANDLE       PIC S9(9) BINARY.
*
CALL "GSFNRANG" USING GSID, RANGE-HANDLE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

RANGE-HANDLE   Pointer to a segment/range handle. Returns a valid handle to the next range object, if there is one. Input, Output.

Return Values

GS-SUCCESS    Found a match.

GS-NOT-FOUND    Did not find a match.

GS-ERROR   An error occurred, use GSERRGET to obtain more information.

Prerequisites

GSFFSEG and GSCLEAR

Notes

This procedure continues to find objects that match the criteria specified in GSFFRANG.

If GeoStan finds a matching segment, you can retrieve the data for that segment using GSHGET.

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.

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

GSFNSEG

Finds the next segment that meets the search criteria.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 SEGMENT-HANDLE       PIC S9(9) BINARY.
*
CALL "GSFNSEG" USING GSID, SEGMENT-HANDLE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

RANGE-HANDLE   Pointer to a segment/range handle. Returns a valid handle to the next range object, if there is one. Input, Output.

Return Values

GS-SUCCESS    Found a match.

GS-NOT-FOUND    Did not find a match.

GS-ERROR   An error occurred, use GSERRGET to obtain more information.

Prerequisites

GSFFSEG and GSCLEAR

Notes

This procedure continues to find objects that match the criteria specified in GSFFSETG.

If GeoStan finds a matching segment, you can retrieve the data for that segment using GSHGET.

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.

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

GSFNST

Finds the next street 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.
*
CALL "GSFNST" USING GSID, STREET-HANDLE, 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 streetrange handle. Returns a valid handle to the next street, if there is one. Input, Output.

Return Values

GS-SUCCESS    Found a match.

GS-NOT-FOUND    Did not find a match.

GS-ERROR   An error occurred, use GSERRGET to obtain more information.

Prerequisites

GSFFST and GSCLEAR

Notes

This procedure continues to find objects that match the criteria specified in GSFFST.

If GeoStan finds a matching segment, you can retrieve the data for that segment using GSHGET.

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.

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

GSFSTAT

Returns if the file successfully opened, and the date of the USPS data used in generating the primary GSD file.

Syntax

01 GSID                             PIC S9(9) BINARY.
01 STATE-CODE                      PIC X(2).
01 GSFUNSTAT                   PIC 9(4) BINARY.
01 BUILD-DATE                       PIC 9(4) COMP-5.
*
CALL "GSFSTAT" USING GSID, STATE-CODE, BUILD-DATE, GSFUNSTAT.

Arguments

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

STATE-CODE   State FIPS or abbreviation (this argument is now ignored). Input

GSFUNSTAT   Return value for the procedure. Output.

BUILD-DATE   Publish date of the USPS data used in the current GeoStan release. Output.

Return Values

Series of bit-flags. The following GS-VARIABLEs are used to test these flags:

GS-AUXILIARY-EXISTS

Opened an auxiliary file (.gsx).

GS-EWS-MATCH-EXISTS

loaded a valid, unexpired EWS file is loaded (ews.txt).

GS-EXP-CENTROIDS-EXISTS

Opened the Expanded Centroids file (us_cent.gsc in MLDB folder).

GS-FILE-EXISTS

Opened a primary GSD file (us.gsd, use.gsd, usw.gsd).

GS-GSL-EXISTS

Opened eLOT and Z4Change dataa(us.gsl).

GS-REV-PBKEY-EXISTS

Opened a Reverse PreciselyID Lookup file (*.pbk in MLDR folder)b

GS-STATEWIDE-EXISTS

Initialized a state-wide intersection file (us.gsi, use.gsi, usw.gsi).

GS-SUPP-EXISTS

Opened a supplemental GSD file. (ust.gsd, uste.gsd, uswt.gsd)

GS-ZIP9-IDX-EXISTS

Opened a ZIP9 index file (ZIP9.gsu, ZIP9e.gsu, ZIP9w.gsu).

GS-ZIPMOVE-EXISTS

Opened a ZIPMove datab (us.gsz).

aeLOT data requires an additional license. However, the Z4Change data is always enabled.

bYou must have an additional license to use this file.

Prerequisites

GSINITWP

Example

The following is an example of how to obtain the month/day/year from the build date:

01 GSID                   PIC S9(9) BINARY.
01 STATE-CODE             PIC X(2).
01 GSFUNSTAT              PIC S9(4) BINARY.
01 BUILD-DATE             PIC 9(4) COMP-5.
 
01 BUILD-YEAR             PIC 9(4).
01 BUILD-MONTH            PIC 9(4).
01 BUILD-DAY              PIC 9(4).
CALL "GSFSTAT" USING GSID, STATE-CODE, BUILD-DATE, GSFUNSTAT.

5  Divide BUILD-DATE by 384 giving BUILD-YEAR remainder build-month.

6  Add 1990 to BUILD-YEAR.

7  Divide BUILD-MONTH by 32 giving BUILD-MONTH remainder BUILD-DAY.

8  Add 1 to BUILD-MONTH.

– or –

9  Compute BUILD-YEAR = (BUILD-DATE/384)+1990

10  Compute BUILD-MONTH = ((BUILD-DATE-((BUILD-YEAR-1990)*384)/32)+1

11  Compute BUILD-DAY = BUILD-DATE-((BUILD-YEAR-1990)*384)-((BUILD-MONTH-1)*32)

GSFSTATX

Returns information about current GeoStan data set and license.

Syntax

01 GSID                             PIC S9(9) BINARY.
01 OPTION                   PIC S9(9) BINARY.
01 GSFUNSTAT                        PIC 9(9) BINARY.
01 OUTLEN                           PIC 9(9) BINARY.
01 OUTPUT-STRING                    PIC X(USER LEN).
*
CALL "GSFSTATX" USING GSID, OPTION, OUTPUT-STRING, OUTLEN, GSFUNSTAT.

Arguments

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

OPTION   Specific information to return. The following table includes the types of information available. Input.

GS-STATUS-DATATYPE-NUM

GS-SUCCESS or GS-ERROR.GeoStan places the retrieved information in the buffer. See the Return Values section of this procedure for the returned numeric values.

GS-STATUS-DATATYPE-STR

GS-SUCCESS or GS-ERROR. GeoStan places this information in the buffer.

GS-STATUS-DATUM-NUM

Numeric values listed in the Return Values section of this procedure.

GS-STATUS-DATUM-STR

The NAD used natively by the data. It does not reflect the datum currently in use by GeoStan. See GSGDATUM and GSSDATUM for further information on setting the returned NAD.

GS-STATUS-DAYS-REMAINING

•DAYS-UNLIMITED or the number of days remaining before the expiration of the license for unmetered licenses and unlimited licenses.

•Days remaining before license expiration for metered limited licenses.

GS-STATUS-FILE-CHKSUM-NUM

Calculated value (an integer) used to check data integrity. The OUTPUT-STRING and OUTLEN parameters are unused. Set OUTLEN to 0.

GS-STATUS-GEO-RECORD-TOTAL

•0 for unmetered licenses.

•Total number or records geocoded for metered licenses

GS-STATUS-RECORDS-REMAINING

•RECORDS-UNLIMITED for unmetered licenses and metered unlimited licenses.

•Number or records remaining on the license for metered limited licenses

GSFUNSTAT   Return value for the procedure. Output.

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

OUTPUT-STRING    The location to store the returned data. Output.

Return values

The following table shows the return values for the GS-STATUS-DATATYPE-NUM mode.

GS-STATUS-DATATYPE-NUM

Data Type

0

USPS

1

TIGER

2

TomTom street-level data

4

Deprecated

6

HERE (formerly NAVTEQ) street-level data

7

TomTom point-level data

9

Auxiliary file

10

User Dictionary

11

HERE (formerly NAVTEQ) point-level data

12

Master Location Data

 

The following table shows the return values for the GS-STATUS-DATUM-STR mode.

GS-STATUS-DATUM-STR

Data Type

0

NAD27

1

NAD83 (WGS84 for GTD data)

Prerequisites

GSINITWP

GSGCRDX

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 "GSGCRDX" 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 GSGCRDX 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.

GSGLIBV

Returns the current version of the GeoStan library.

Syntax

01 GSFUNSTAT          PIC S9(9) BINARY.
*
CALL "GSGLIBV" USING GSFUNSTAT.

Arguments

GSFUNSTAT   Return value for the procedure. Output.

Return values

n Low Byte = Major version number.

n High Byte = Minor version number.

Prerequisites

GSINITWP

Notes

In general, the major version number changes whenever Precisely adds a new API features, or when the data structures in the GeoStan data files change.

Minor version number changes for each release of GeoStan.

Example

The best way to extract the high and low bytes is to subdefine GSFUNSTAT as follows:

01 GSFUNSTAT PIC S9(9) BINARY.01 GS-MINOR-VERSION PIC 9(2) BINARY.01 GS-MAJOR-VERSION PIC 9(2) BINARY.         CALL "GSGLIBV" USING GSFUNSTAT.      DIVIDE GSFUNSTAT BY 256 GIVING GS-MINOR-VERSION                               REMAINDER MAJOR-VERSION

GSHGCRDX

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 "GSHGCRDX" 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 GSGCRDX 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.

GSHGET

Retrieves data for objects found via GSSFFSG and GSFNRANG.

Syntax

01 GSID                              PIC S9(9) BINARY.
01 GSFUNSTAT                         PIC S9(9) BINARY.
01 RANGE-HANDLE                      PIC S9(9) BINARY.
01 GSOPTIONS                  PIC  9(9) BINARY.
01 OUTPUT-STRING                  PIC X(USER LEN)
01 OUTLEN                  PIC S9(4) BINARY.
CALL "GSHGET" USING GSID, GSOPTIONS, RANGE-HANDLE,OUTPUT-STRING, OUTLEN, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

RANGE-HANDLE   Pointer to the current range handle. Input.

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

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

OUTLEN   Maximum size of the data that 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

GSFFSEG or GSFNRANG

Notes

This procedure retrieves data from the geocode buffer for a given range handle. If you have a street or segment handle, you must convert the handle to a range handle before you can use this procedure.

GSINITWP

Initializes GeoStan using properties.

Syntax

01 INIT-PROP-LIST                  Defined in GEOSTAN copy member.
01 STATUS-PROP-LIST                      Defined in GEOSTAN copy member.
01 GSID                 PIC S9(9) BINARY.
CALL 'GSINITWP' USING INIT-PROP-LIST,STATUS-PROP-LIST, GS-ID.
IF GS-ID EQUAL ZERO DISPLAY '** ERROR ** GEOSTAN FAILED TO INITIALIZE’ PERFORM GET-ERROR-MSG

Arguments

INIT-PROP-LIST, STATUS-PROP-LIST    Pointer to property list structure. Input.

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

GSINITWP property options:

Property Name

Description

GS-INIT-CACHESIZE

Relative cache size used by GeoStan. Controls the amount of memory that GeoStan allocates to store temporary street data during address processing. A smaller cache may slow the performance of GeoStan. A cache size of 2 gives best performance, but uses more memory. Values: 0, 1 or 2.

GS-INIT-DATAPATH

List of paths to search for necessary files.

GS-INIT-DPV

Initialize DPV.

GS-INIT-DPV-DATA-ACCESS

Indicates the type of files to load and how to access the files. The following contains the possible values.

• DPV-DATA-FULL-FILEIO — dpvh.db accessed via file I/O and Micro (U) memory model. This is a default value.

• 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. 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 of I/O requests that normally occurs when you use the full DPV data. file.

• 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-INIT-DPV-DIRECTORY

String that specifies the directory containing DPV data.

GS-INIT-DPV-SECURITYKEY

Security key for product authorization.

GS-INIT-FILE-MEMORY-LIMIT

Note: This property only applies to 64-bit applications.

When GeoStan is initialized, it will memory-map as many data files into memory as the GS-INIT-FILE-MEMORY-LIMIT allows. The default value of 16 GB is sufficient for memory-mapping two streets and two points datasets. Memory mapping your data files can provide a 10-15% performance improvement compared to mapping none of them. However, if your environment has memory constraints, you can set the GS-INIT-FILE-MEMORY-LIMIT to the number of megabytes you can afford.

This initialization property can only be set once per GeoStan executable process. If you attempt to set this property again (i.e., on a separate thread), the request is ignored.

If all of the data files cannot be memory-mapped in the space provided, the status property GS-STATUS-FILE-MEM-SYS-EXCDD is set to true. To see how much virtual memory is being used for memory-mapping data files, query the status property GS-STATUS-MEMORY-USED.

GS-INIT-GEOSTAN-ID

If NULL, this means initialize GeoStan.

GS-INIT-GSVERSION

GeoStan version.

GS-INIT-LACSLINK

Initialize LACSLink.

GS-INIT-LACSLINK-DIRECTORY

Directory of LackLink data.

GS-INIT-LACSLINK-SECURITY-KEY

Security key.

GS-INIT-LICFILENAME

License file name.

GS-INIT-OPTIONS-ADDR-CODE

Open files needed for address standardization and geocoding.

GS-INIT-OPTIONS-SPATIAL-QUERY

Open spatial query files.

GS-INIT-OPTIONS-Z9-CODE

Open files needed for ZIP centroid geocoding.

GS-INIT-OPTIONS-ZIP-PBKEYS

Open the file needed to return PreciselyIDs for ZIP centroid locations in Master Location Data. If the ZIP centroid file (zipsmld.gsd) that contains PreciselyIDs loaded successfully, GS-STATUS-FILE-ZIP-PBKEYS is True. (Default value = False).

When an address point is not available for an address in Master Location Data, this option returns a ZIP centroid and the PreciselyID unique identifier, which can be used to unlock additional information about an address using GeoEnrichment data.

To enable returning PreciselyIDs for ZIP centroid locations in MLD, the GS-FIND-Z-CODE GSFINDWP property needs to be enabled. If it is not enabled, an "E" location code is returned and the results data will not include a geocode nor PreciselyID.

GS-INIT-PASSWORD

License password.

GS-INIT-RDI-DIRECTORY

Directory containing Residential Delivery Indicator (RDI) data file, rdi.db. Max 255 characters. Requires Delivery Point Validation (DPV).

GS-INIT-RELDATE

String of the latest data to use in initialization.

GS-INIT-SUITELINK

Initializes SuiteLink 

GS-INIT-SUITELINK-DIRECTORY

Directory containing SuiteLink data.

GS-INIT-Z4FILE

Name of the ZIP +4 directory file, us.z9.

Return Values

Returns the ID of the GeoStan instance that was initialized.

Prerequisites

GSPLSTCRandGSPSET*

Notes

Initializes GeoStan using a property list. Upon return, this function utilized the properties, but left the property list intact. The application owns the property lists. The status property list is guaranteed to contain properties for all defined status properties with their values properly set.

GSINITWP can be used to initialize GeoStan, DPV, and LACSLink with a single call (if the appropriate initialization properties are in the init list). When this function successfully completes, it populates the GS-INIT-GEOSTAN-ID property in the property list referred to by the pInitProps parameter with the actual GeoStan ID.

If you invoke this function with the GeoStan ID property pre-set to a valid GeoStan ID, it will not attempt to re-initialize GeoStan. This is how GSINITWP can be used to initialize DPV and/or LACSLink after GeoStan has already been initialized with a previous call to GSINITWP. If you intend to reuse the same initialization property list to initialize GeoStan several times you must reset the GS-INIT-GEOSTAN-ID property back to zero, or completely remove the property from the list. This informs GeoStan that you want a new GeoStan instance when you call GSINITWP.

These initialization properties are required for GSINITWP to function correctly:

  • GS-INIT-LICFILENAME

  • GS-INIT-DATAPATH

  • GS-INIT-PASSWORD

These initialization properties are recommended, but not required:

  • GS-INIT-Z4FILE (required for ZIP centroid matching).

  • GS-INIT-OPTIONS-Z9-CODE (required for ZIP centroid matching).

  • GS-INIT-CACHESIZE (to improve GeoStan performance).

  • GS-INIT-OPTIONS-ADDR-CODE (required for address matching).

  • GS-INIT-OPTIONS-SPATIAL-QUERY (required for reverse geocoding and the MBR-related functions).

All other available initialization properties are entirely optional.

GSLACCLS

Clears the LACSLink global statistics.

Syntax

01 GSID             PIC 9(9) BINARY.
01 RETURN-CODE             PIC 9(9) BINARY
 
CALL "GSLACCLS" USING GSID, RETURN-CODE.

Arguments

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

RETURN-CODE   Size of the GSLACGCS data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

Prerequisites

GSLACINR

GSLACFPD

Formats a LACSLink false positive detail record from GSLACGFH.

Syntax

01 GSID       PIC 9(9) BINARY.
01 GS-FALSE-POS-DETAIL-DATA
01 RETURN-CODE       PIC 9(9) BINARY.
01 HEADER            PIC X(len).
01 HEADER-SIZE       PIC 9(9) BINARY VALUE len.
CALL "GSLACFPD" USING GSID, GS-FALSE-POS-DETAIL-DATA, GS-FPHD-SIZE, HEADER, HEADER-SIZE, RETURN-CODE

Arguments

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

GS-FALSE-POS-DETAIL-DATA    Pointer to the LACSLink report data structure. This value is completed by GSLACGFD. Input.

RETURN-CODE   Size of the LACSLink report data structure. Input.

HEADER   Buffer containing the LACSLink false positive header after GSLACFPD successfully completes. When the GeoStan application writes the false positive report, it writes this buffer to the last line of the file. Output.

HEADER-SIZE   Length of the detail buffer. Input.

Return Values

GS-SUCCESS 

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING    Call GSERRGTX for more information.

Prerequisites

GSLACGFD

GSLACFPH

Formats a LACSLink false positive header record with data from GSLACGFH.
Note: If singleline address input is used, the output from GSLACFPH will be incorrect.

Syntax

01 GSID          PIC 9(9) BINARY.
01 PDATA         PIC ????
01 RETURN-CODE          PIC 9(9) BINARY.
01 HEADER               PIC X(len).
01 HEADER-SIZE          PIC 9(9) BINARY VALUE len.
 
CALL "GSLACFPH" USING GSID, GS-FALSE-POS-HEADER-DATA, GS-FPHD-SIZE, HEADER, HEADER-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-HEADER-DATA    Pointer to the LACSLink report data structure. GSLACGFD completes this value. Input.

RETURN-CODE   Size of GSLACFPH data structure. Input.

HEADER   Buffer containing the LACSLink false positive header after GSLACFPH successfully completes. When the GeoStan application writes the false positive report, it writes this buffer to the first line of the file. Output.

HEADER-SIZE   Length of the header buffer. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSLACGFD
GS-DPV-FALSE-POS == "Y"

GSLACGCS

Obtains the complete LACSLink statistics since the application initialized LACSLink.
Note: If singleline address input is used, the output from GSLACGCS will be incorrect.

Syntax

01 GSID             PIC 9(9) BINARY.
01 GS-LACS-COMPLETE-STATS
01 RETURN-CODE             PIC 9(9) BINARY
 
CALL "GSLACGCS" USING GSID, GS-LACS-COMPLETE-STATS, GS-LCS-SIZE, RETURN-CODE.

Arguments

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

GS-LACS-COMPLETE-STATS    Retrieves LACSLink statistics since the application initialized LACSLink. This structure contains the following:

GS-LCS-NTOTAL-AMATCHES    Total number of records matched through LACSLink. Output.

GS-LCS-NTOTAL-PROCESSED    Total number of records processed through LACSLink. Output.

GS-LCS-NTOTAL-00MATCHES    Total number or records not matched through LACSLink. Output.

GS-LCS-NTOTAL-09MATCHES    Total number of records converted through LACSLink, but no new address provided. Output.

GS-LCS-NTOTAL-14MATCHES    Total number of records converted through LACSLink. Output.

GS-LCS-NTOTAL-93MATCHES    Total number of records matched through LACSLink where GeoStan drops the unit number. Output.

RETURN-CODE   Size of the GSLACGCS data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSLACINR

GSLACGFD

Retrieves the detail record for a LACSLink false positive report.

Syntax

01 GSID                PIC 9(9) BINARY.
01 GS-FALSE-POS-DETAIL-DATA
01 RETURN-CODE                PIC 9(9) BINARY.
 
CALL "GSLACGFD" USING GSID, GS-FALSE-POS-DETAIL-DATA, GS-FPDD-SIZE, RETURN-CODE.

Arguments

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

*PDATA   Retrieves LACSLink statistics from the detail record for false positive address matches using the data passed in GSLACGFH. This structure contains the following:

GS-FPDD-ADDRESS-PRIMARY-NUMBER    House number. Output.

GS-FPDD-ADDRESS-SECONDARY-ABBREVIATION    Unit type (APT, SUITE, LOT). Output.

GS-FPDD-ADDRESS-SECONDARY-NUMBER    Unit number. Output.

GS-FPDD-MATCHED-ZIP-CODE    ZIP Code. Output.

GS-FPDD-MATCHED-PLUS    ZIP Code extension. Output.

GS-FPDD-POST-DIRECTIONAL    Street name postdirectional (N, S, E, W). Output.

GS-FPDD-STREET-NAME    Name of the street. Output.

GS-FPDD-STREET-PREDIR    Street name predirectional (N, S, E, W). Output.

GS-FPDD-SUFFIX-ABBREVIATION    Street type (AVE, ST, RD). Output.

FILLER   Reserved for future implementation. Output.

return-code   Size of the GSLACGFH data structure. Input.

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSLACINR
GS-LACSLINK-IND == "F"

GSLACGFH

Retrieves LACSLink statistics for the header record for a LACSLink false positive report.
Note: If singleline address input is used, the output from GSLACGFH will be incorrect.

Syntax

01 GSID                PIC 9(9) BINARY.
01 GS-FALSE-POS-HEADER-DATA
01 RETURN-CODE                PIC 9(9) BINARY.
 
CALL "GSLACFPH" USING GSID, GS-FALSE-POS-HEADER-DATA, GS-FPHD-SIZE, RETURN-CODE.

Arguments

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

GS-FALSE-POS-HEADER-DATA    Retrieves LACSLink statistics from the header record for false positive address matches using the data passed in GSLACGFD. This structure contains the following:

GS-FPDD-MAILERS-ADDRESS-LINE    Address of the mailer. Input.

GS-FPDD-MAILERS-CITY-NAME    City of the mailer. Input.

GS-FPDD-MAILERS-COMPANY-NAME    Name of the mailer. Input.

GS-FPDD-MAILERS-STATE-NAME    State of the mailer. Input.

GS-FPHD-MAILERS9-DIGIT-ZIP    ZIP Code of the mailer. Input.

GS-FPDD-NTOTAL-PROCESSED    Number of records processed through LACSLink. Output.

GS-FPDD-NTOTAL-MATCHED    Number of records confirmed through LACSLink. Output.

GS-FPDD-NUMBER-FALSE-POS    Number of LACSLink false positives found. Output.

GS-FPDD-NUMBER-ZIP-ON-FILE    Number of distinct ZIP Codes processed through LACSLink. Output.

GS-FPDD-TOTAL-ZIP4-MATCHED    Number of records that have matched with ZIP + 4. Output.

RETURN-CODE   Size of the GSLACGFD data structure. Input

Return Values

GS-SUCCESS

GS-ERROR   Call GSERRGTX for more information.

GS-WARNING   Call GSERRGTX for more information.

Prerequisites

GSLACINR
GS-LACSLINK-IND == "F"

GSMGET

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.

GSMGH

Returns the range handle for the match candidate item specified.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 INDEX              PIC 9(4) BINARY.
01 RANGE-HANDLE       PIC S9(9) BINARY.
*
CALL "GSMGH" USING GSID, INDEX, RANGE-HANDLE, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

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

RANGE-HANDLE   Range handle for the possible match entry. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSNMULT

Notes

This procedure can to extract more information about a possible match, then GSMGET. It retrieves the range handle for the possible match indicated by the entry argument. Once you have the correct range handle, you can retrieve information by using GSHGET. For a list of elements returned by GSMGET or GSHGET, see Variables for storing and retrieving data.

GSNMULT

Returns the number of match candidates found.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

A positive value indicates the number of match candidates. GS-ERROR indicates an error.

Prerequisites

GSSFINDWP

Notes

This procedure returns the number of match candidates found. Use GSMGET to retrieve the actual address elements for each possible match. A return code from GSSFINDWP indicates a possible match.

GSPFIND

Finds a property in a property list.

Syntax

01 FIND-PROP-LIST           PIC S9(9) BINARY.
01 PROPENUM                    PIC S9(9) BINARY.
01 GSFUNSTAT                  PIC S9(9) BINARY.
*
CALL "GSPFIND" USING FIND-PROP-LIST, PROPENUM, GSFUNSTAT.

Arguments

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

PROPENUM   The ID of the property to find. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

GS-SUCCESS returns if the property is found in the property list. GS-ERROR returns if the property is not found.

GSPFIRST

Sets property iterator to first property.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

Prior to iterating through the properties in a property list, this procedure sets the property list iterator to the beginning of the list.

GSPFNEXT

Iterates to the next sequential property in the property list.

Syntax

01 FIND-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                PIC S9(9) BINARY.
01 PROPVALUE               PIC S9(9) BINARY.
01 GSFUNSTAT               PIC S9(9) BINARY.
*
CALL "GSPFNEXT" USING FIND-PROP-LIST, PROPENUM, PROPVALUE, GSFUNSTAT.

Arguments

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

PROPENUM   The ID of the property to find. Input.

PROPVALUE   Pointer to union of property values. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

GeoStan only populates one of the PropValue union members. The populated union member depends on the property output type. If there is no "next" entry, GeoStan returns an error.

GSPGETB

Retrieves a boolean property.

Syntax

01 STATUS-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                  PIC S9(9) BINARY.
01 QBOOL                     PIC S9(9) BINARY.
01 GSFUNSTAT                 PIC S9(9) BINARY.
*
CALL "GSPGETB" USING STATUS-PROP-LIST, PROPENUM, QBOOL, GSFUNSTAT.

Arguments

STATUS-PROP-LIST   Pointer to property list structure defined in copy member GEOSTAN. Input.

PROPENUM   The ID of the property to find. Input.

QBOOL   The boolean value of the property. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPGETD

Retrieves a double property.

Syntax

01 STATUS-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                      PIC S9(9) BINARY.
01 DOUBLE                        PIC S9(9) BINARY.
01 GSFUNSTAT                     PIC S9(9) BINARY.
*
CALL "GSPGETD" USING STATUS-PROP-LIST, PROPENUM, DOUBLE, GSFUNSTAT.

Arguments

STATUS-PROP-LIST   Pointer to property list structure defined in copy member GEOSTAN. Input.

PROPENUM   The ID of the property to find. Input.

DOUBLE   The double value of the property. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPGETL

Retrieves an integer property.

Syntax

01 STATUS-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                      PIC S9(9) BINARY.
01 INTL               PIC S9(9) BINARY.
01 GSFUNSTAT                     PIC S9(9) BINARY.
*
CALL "GSPGETL" USING STATUS-PROP-LIST, PROPENUM, INTL, GSFUNSTAT.

Arguments

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

PROPENUM   The ID of the property to find. Input.

INTL   Long value. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPGETST

Retrieves a string property.

Syntax

01 STATUS-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                      PIC S9(9) BINARY.
01 INTL                   PIC S9(9) BINARY.
01 GSFUNSTAT                     PIC S9(9) BINARY.
*
CALL "GSPGETST" USING STATUS-PROP-LIST, PROPENUM, PROPVALUE, GSFUNSTAT.

Arguments

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

PROPENUM   The ID of the property to find. Input.

INTL   Long value. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPGINFO

Retrieves information about a property.

Syntax

01 PROPENUM        PIC S9(9) BINARY.
01 INT             PIC S9(9) BINARY.
01 PROPLISTTYPE    PIC S9(9) BINARY.
01 PSTR            PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPGINFO" USING PROPENUM, INT, PROPLISTTYPE, PSTR, GSFUNSTAT.

Arguments

PROPENUM   The ID of the property to find. Input.

INT   Output.

PROPLISTTYPE   Pointer to property list structure. Input.

PSTR   Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPGSTRL

Retrieves the length of the string value of a property.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 INTLU           PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPGSTRL" USING PROPLIST, PROPENUM, INTLU, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input.

PROPENUM   The ID of the property to find. Input.

INTLU   Required string buffer length. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPLSTCR

Creates and initializes a property list for GeoStan initialization.

Syntax

01 INIT-PROP-LIST                 PIC S9(9) BINARY.
01 GS-INIT-PROP-LIST-TYPE             PIC S9(9) BINARY.
01 GSFUNSTAT                PIC S9(9) BINARY.
*
CALL "GSPLSTRCR" USING INIT-PROP-LIST, GS-INIT-PROP-LIST-TYPE, GSFUNSTAT.

Arguments

INIT-PROP-LIST   Pointer to property list structure defined in copy member GEOSTAN. Input and Output.

GS-INIT-PROP-LIST-TYPE   Pointer to property list structure defined in copy member GEOSTAN. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Notes

This procedure creates/initializes a property list for use in GSINITWP or GSFINDWP. Any property list created by this function needs to eventually be destroyed with GSPLSTDE.

GSPLSTRD

Reads the property list from a file or a character string.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 GS-CONST-STR    PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPLSTRD" USING PROPLIST, NULL, GS-CONST-STR, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Output.

GS-CONST-STR   The string buffer containing the properties to read. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPLSTDE

Destroys a property list.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPLSTDE" USING PROPLIST, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

Find property lists cannot be destroyed until all searching is complete. Any list created by GSPLSTCR must eventually be destroyed with GSPLSTDE.

GSPLSTGC

Retrieves the number of properties in a property list.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 INTL            PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPLSTGC" USING PROPLIST, INTL, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

INTL   Returned count. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPLSTWR

Writes the property list to a file or a character string.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 GS-CONST-STR    PIC S9(9) BINARY.
01 PSTR            PIC S9(9) BINARY.
01 INTSU               PIC S9(9) BINARY
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPSETAS" USING PROPLIST, GS-CONST-STR, PSTR, INTSU, GSFUNSTAT.

Arguments

PROPLIST    Pointer to property list structure. Input and Output.

gs-const-str    The string name of the property to set. Input.

PSTR   Output.

INTSU   Output.

GSFUNSTAT    Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

If the outfile argument value is "stdout", then this function writes the properties to standard out. If the outfiles argument is NULL, then this function writes the properties to the pBuffer string.

GSPREMOV

Removes a property from the property list.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPREMOV" USING PROPLIST, PROPENUM, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

PROPENUM   Property ID. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPRESET

Resets the property list to its default state.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPRESET" USING PROPLIST, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

Depending on the type of property list, this might mean "empty" (init and status properties) or refill it with some needed defaults (find properties).

GSPSETAS

Sets a property where input name and value are both strings.

Note: If you intend to use the same Find property settings for all your address records, try to construct your application to set the Find properties once before processing. It is unnecessary to reset the properties again to the same values for each address record. However, if required, you can change Find property values for individual searches. Performance may be negatively affected by resetting for individual record searches. Reset Find properties between address searches only if changing the Find property value is necessary.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 GS-CONST-STR    PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 GS-CONST-STR    PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPSETAS" USING PROPLIST, GS-CONST-STR, GS-CONST-STR, GSFUNSTAT.

Arguments

PROPLIST    Pointer to property list structure. Input and Output.

gs-const-str    The string name of the property to set. Input.

PROPENUM   Property ID. Input.

gs-const-str    The string value of the property. Input.

GSFUNSTAT    Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

Notes

This procedure performs the conversion to correct property variable ID and property value type. If the input property name is a NULL pointer, the property ID is for use in identifying the property instead. If both property name and property ID are present, preference is given to the property name, ignoring the property ID.

GSPSETB

Sets a boolean property.

Note: If you intend to use the same Find property settings for all your address records, try to construct your application to set the Find properties once before processing. It is unnecessary to reset the properties again to the same values for each address record. However, if required, you can change Find property values for individual searches. Performance may be negatively affected by resetting for individual record searches. Reset Find properties between address searches only if changing the Find property value is necessary.

Syntax

01 FIND-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                    PIC S9(9) BINARY.
01 QBOOL                 PIC S9(9) BINARY.
01 GSFUNSTAT                   PIC S9(9) BINARY.
*
CALL "GSPSETB" USING FIND-PROP-LIST, PROPENUM, QBOOL, GSFUNSTAT.

Arguments

FIND-PROP-LIST    Pointer to property list structure defined in copy member GEOSTAN. Input and Output.

PROPENUM   Property ID. Input.

QBOOL   Boolean value. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPSETD

Sets a double property.

Syntax

01 STATUS-PROP-LIST        PIC S9(9) BINARY.
01 PROPENUM                      PIC S9(9) BINARY.
01 DOUBLE                        PIC S9(9) BINARY.
01 GSFUNSTAT                     PIC S9(9) BINARY.
*
CALL "GSPSETD" USING STATUS-PROP-LIST, PROPENUM, DOUBLE, GSFUNSTAT.

Arguments

STATUS-PROP-LIST   Pointer to property list structure defined in copy member GEOSTAN. Input.

PROPENUM   The ID of the property to find. Input.

DOUBLE   The double value of the property. Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPSETL

Sets an integer property.

Note: If you intend to use the same Find property settings for all your address records, try to construct your application to set the Find properties once before processing. It is unnecessary to reset the properties again to the same values for each address record. However, if required, you can change Find property values for individual searches. Performance may be negatively affected by resetting for individual record searches. Reset Find properties between address searches only if changing the Find property value is necessary.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 INTL            PIC S9(9) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPSETL" USING PROPLIST, PROPENUM, INTL, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

PROPENUM   Property ID. Input.

INTL   Long value. Input and Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPSETS

Sets a short integer property.

Note: If you intend to use the same Find property settings for all your address records, try to construct your application to set the Find properties once before processing. It is unnecessary to reset the properties again to the same values for each address record. However, if required, you can change Find property values for individual searches. Performance may be negatively affected by resetting for individual record searches. Reset Find properties between address searches only if changing the Find property value is necessary.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 INTS            PIC S9(4) BINARY.
01 GSFUNSTAT       PIC S9(9) BINARY.
*
CALL "GSPSETS" USING PROPLIST, PROPENUM, INTS, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

PROPENUM   Property ID. Input.

INTS   Short value. Input and Output.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSPSETST

Sets a string property.

Note: If you intend to use the same Find property settings for all your address records, try to construct your application to set the Find properties once before processing. It is unnecessary to reset the properties again to the same values for each address record. However, if required, you can change Find property values for individual searches. Performance may be negatively affected by resetting for individual record searches. Reset Find properties between address searches only if changing the Find property value is necessary.

Syntax

01 PROPLIST        PIC S9(9) BINARY.
01 PROPENUM        PIC S9(9) BINARY.
01 C-CHARACTER-STRING.
05 CHAR-STRING  PIC X(user len) VALUE 'your string here'.
05  FILLER      PIC X(01) VALUE X'00'.
*
CALL "GSPSETST" USING PROPLIST, PROPENUM, C-CHARACTER-STRING, GSFUNSTAT.

Arguments

PROPLIST   Pointer to property list structure. Input and Output.

PROPENUM   Property ID. Input.

C-CHARACTER-STRING    String value. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSPLSTCR

GSSCACHE

Sets the size of the cache GeoStan uses.

Syntax

01 SIZE               PIC S9(9) BINARY.
*
CALL "GSSCACHE" USING SIZE.

Arguments

SIZE   Size to set cache. Input

.

Value

Cache Size

0

Small

1

Medium

2

Large

Notes

You must call GSSCACHE before GSINITWP.

A smaller cache may slow the performance of GeoStan. Precisely recommends a cache size of 2 for the best performance.

For changes in cache size settings to take effect, call GSSCACHE before GSINITWP.

GSSETSEL

Allows you to select a match from a set or match candidates.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT             PIC S9(9) BINARY.
01 INDEX              PIC 9(4) BINARY.
*
CALL "GSSETSEL" USING GSID, INDEX, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

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

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSMGET

Notes

After GSFINDWP returns GS-ADDRESS-NOT-RESOLVED, use GSNMULT and GSMGET to determine which possible match is the correct match. Then use GSSETSEL to load that possible match into the data retrieval buffers and retrieve it using GSDATGET.

This procedure returns GS-ERROR if the selection is out of range.

GSSLIC

Identifies license file and key.

Syntax

01 PASSWORD               PIC S9(9) BINARY.
01 FILE-NAME               PIC X(12).
*
CALL "GSSLIC" USING PASSWORD, FILE-NAME.

Arguments

PASSWORD   Long integer used as a unique key. Input.

FILE-NAME   Fully qualified file name, including drive and path, of the file containing the license information. Input.

Notes

Must call GSSLIC before GSINITWP.

GSSRELD

Allows you to specify the oldest acceptable date for GeoStan data files.

Syntax

01 RELEASE-DATE       PIC X(8).
01 LSTATUS            PIC 9(9) BINARY.
*
CALL "GSSRELD" USING RELEASE-DATE, LSTATUS.

Arguments

RELEASE-DATE   Oldest allowable date for GeoStan data files, in the format yyyymmdd. Input.

LSTATUS   Return code. Output.

Return Values

Date and time given in RELEASE-DATE as a binary number. This binary value is the number of seconds that have elapsed since January 1, 1970.

Notes

Must be called before GSINITWP.

Ignores any data files with dates older than the RELEASE-DATE parameter.

GSSNDX

Generates a soundex key for use in GSFFSET.

Syntax

01 LSTATUS          PIC 9(9) BINARY.
01 NAME             PIC X(USERLEN).
*
CALL "GSSNDX" USING NAME, LSTATUS.

Arguments

NAME   String to convert to a soundex key. Input.

LSTATUS   Return code. Output.

Return Values

Soundex key

Notes

This procedure generates a soundex key for a street name. Use it in conjunction with GSFFSEG when you want to perform a soundex search. The soundex key, when combined with a locale (state and city), is the primary index into the GeoStan databases. Searching by soundex allows you to use your own scoring and matching mechanism for geocoding.

Note: A soundex match is a match based on the pronunciation of a field, not on the spelling of a field.

GeoStan uses a modified version of the standard soundex algorithm first published by Donald Knuth. The modifications made by Precisely include special treatment of certain prefixes such as MAC, KN, and WR; special treatment for numeric street names; and an encoding scheme to pack the key into the smallest number of bits.

GSSSELR

Allows GeoStan to use a record found outside of GSSFINDWP as a match.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 GSOPTIONS          PIC S9(9) BINARY.
01 RANGE-HANDLE       PIC S9(9) BINARY.
*
CALL "GSSSELR" USING GSID, RANGE-HANDLE, GSOPTIONS,
GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

RANGE-HANDLE   Range pointer of object to return as a match. A range record indicates a range of addresses such as "2800 – 2900 Center Green Drive". Input.

GSOPTIONS   The following table contains the valid variables. Input.

GS-ADDR-CODE

Attempts to standardize and find an address geocode. You must set this switch for address standardization. If this switch is not set, GeoStan uses only the input ZIP and ZIP + 4 address elements.

GS-WIDE-SEARCH

GeoStan considers all records matching the first letter of the street name, rather than the soundex key on the street name. This results in a wider search.

GS-FINANCE-SEARCH

When you add GS_FINANCE_SEARCH, GeoStan searches the entire Finance Area for possible streets. These modifiers have no meaning when doing a ZIP centroid match.

GS-Z9-CODE

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

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 match based on all possible ZIP centroids available.

If you specify GS_ADDR_CODE and a ZIP centroid option, GeoStan only returns a ZIP Code centroid match if an address geocode is not available.

You must use either GS_ADDR_CODE or GS_Z_CODE or both.(In general, you should specify both.) These option settings are additive.

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

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSFFSEG

Notes

This procedure allows you to get a range handle which points to the address range you want to match to. Use this command to indicate that GSSFINDWP found the match, when in fact the match is set to whichever range handle is passed through the RANGE-HANDLE argument. You must specify the GSOPTIONS variable so that subsequent calls to GSDATGET have the type of location information to return.

This procedure returns standardized results from a list generated by GSFFSEG / GSFNRANG. This procedure performs a query procedure that lets the user choose from a list of possible matches.

GSTERM

Terminates GeoStan.

Syntax

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

Arguments

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

GSFUNSTAT   Contains the return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Notes

You must call GSTERM at the conclusion of a session to close files and release other resources. It closes GeoStan and invalidates GSID. You cannot call any function except GSINITWP after GSTERM.

GSTSTRNG

Determines whether a house number falls within a range.

Syntax

01 GSID               PIC S9(9) BINARY.
01 GSFUNSTAT          PIC S9(9) BINARY.
01 NUM-STRING         PIC X(user len).
01 NUM-RANGE-LO       PIC X(user len).
01 NUM-RANGE-HI       PIC X(user len).
*
CALL "GSTSTRNG" USING GSID, NUM-STRING, NUM-RANGE-LO,NUM-RANGE-HI, GSFUNSTAT.

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

NUM-STRING   House number to test. Input.

NUM-STRING-LO    Low house number in the range. Input.

NUM-STRING-HI    High house number in the range. Input.

Return Values

Non-zero   Number is within the range.

0   Number is not within the range or the comparison cannot be made.

Prerequisites

GSINITWP

Notes

This procedure tests to see if the house number is within the range defined by NUM-STRING-HI and NUM-STRING-LO. It handles all valid house number patterns, such as

123

123A

A123

1A23

A1B23

1A23B

1-23

AB

 

 

   

This procedure uses USPS rules defined in Publication 28, "Postal Addressing Standards", for determining whether number is in range or not. Some patterns are not comparable with other patterns; for example, 123 is not comparable to a range of 1A01 to 1A99.

GSVAUXR

Validates an auxiliary file record.

Syntax

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

Arguments

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

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS    The record is valid and GeoStan will load the record. This includes comment records; records whose first character is a semicolon.

GS-WARNING   The record contains a non-fatal error and GeoStan will load the record. Because this record has a problem, an input address may not be able to match to the record in its current state, or the output data from a match to the record may not be valid.

GS-ERROR    The record contains a fatal error and GeoStan will NOT load the file.

Prerequisites

GSINITWP

GSVGSDDT

Validates the presence of data for specified states in the GSD data file.

Syntax

01    GSID                  PIC S9(9) BINARY.
01    STATES                  OCCURS 100 TIMES.
         05    STATE-CODE         PIC X(3).
         05    STATE-COUNT         PIC S9(9) BINARY.
01 GSFUNSTAT                     PIC S9(9) BINARY.
 
CALL "GSVGSDDT" USING GSID, STATES, GSFUNSTAT.

Arguments

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

STATES   Structure containing the list of state abbreviations and/or FIPS codes. Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS   All states specified in STATES are present in the GSD data.

GS-GSD-DATA-MISSING    One or more states specified in STATES are not present in the GSD data.

GS-ERROR    STATES structure is invalid.

Notes

If GeoStan did not find the GSD primary data for all the specified states, this function creates an error in the error list retrievable using GSERRGTX. The error message code is 114 and the error message is "NO GSD DATA FOUND FOR STATE" and indicates which states GeoStan did not find.

The state abbreviations and corresponding state FIPS codes are as follows:

State

Abbrev.

FIPSCodeaa

State

Abbrev.

FIPSCodea

Alabama

AL

1

New Jersey

NJ

34

Alaska

AK

2

New Mexico

NM

35

Arizona

AZ

4

New York

NY

36

Arkansas

AR

5

North Carolina

NC

37

California

CA

6

North Dakota

ND

38

Colorado

CO

8

Ohio

OH

39

Connecticut

CT

9

Oklahoma

OK

40

Delaware

DE

10

Oregon

OR

41

District of Columbia

DC

11

Pennsylvania

PA

42

Florida

FL

12

Rhode Island

RI

44

Georgia

GA

13

South Carolina

SC

45

Hawaii

HI

15

South Dakota

SD

46

Idaho

ID

16

Tennessee

TN

47

Illinois

IL

17

Texas

TX

48

Indiana

IN

18

Utah

UT

49

Iowa

IA

19

Vermont

VT

50

Kansas

KS

20

Virginia

VA

51

Kentucky

KY

21

Washington

WA

53

Louisiana

LA

22

West Virginia

WV

54

Maine

ME

23

Wisconsin

WI

55

Maryland

MD

24

Wyoming

WY

56

Massachusetts

MA

25

American Samoa

AS

60

Michigan

MI

26

Guam

GU

66

Minnesota

MN

27

North Mariana Islands

MP

69

Mississippi

MS

28

Palau

PW

70

Missouri

MO

29

Puerto Rico

PR

72

Montana

MT

30

Virgin Islands

VI

78

Nebraska

NE

31

 

 

 

Nevada

NV

32

 

 

 

New Hampshire

NH

33

 

 

 

aDo not specify Minor Islands (UM, 74) or you will receive an error. This is defined as a FIPS code, but the USPS does not generate data for this code.

The following pseudo FIPS codes support APO and FPO addresses:

Address

Abbrev.

FIPS Code

Armed Forces Europe

AE

57

Armed Forces Pacific

AP

58

Armed Forces Americas

AA

59

GSWECASS

Writes a USPS CASS report based on the specified template.

Syntax

01    GSID               PIC S9(9).         
01    GS-EXTEND-CASS-DATA
01    DATA-SIZE               PIC S9(9)         BINARY.
01    OUTPUT-NAME               PIC X(1).         
01    GSFUNSTAT               PIC S9(9)         BINARY.
 
CALL "GSWECASS" USING GSID, GS-EXTEND-CASS-DATA, DATA-SIZE, OUTPUT-NAME, GSFUNSTAT.

Arguments

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

GSE-XTEND-CASS-DATA    Input structure, defined in the GEOSTAN copybook. Input.

DATA-SIZE   Size of the CASS report data structure. Input.

OUTPUT-NAME   Not used.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-SUCCESS

GS-ERROR

Prerequisites

GSINITWP

Notes

Before running a CASS report, verify you have loaded the GSZ file (ZIPMove data).

This procedure writes the CASS information to the header buffer using the data passed in GSEXTENDCASSDATA. This structure contains the following:

01    GS-EXTEND-CASS-DATA.
05    GS-ECD-STRUCTVERSION             PIC 9(9)    BINARY.
05    GS-ECD-NRECS             PIC 9(9)    bINARY.
05    GS-ECD-NZIP4             PIC 9(9)    BINARY.
05    GS-ECD-NZIP             PIC 9(9)    BINARY.
05    GS-ECD-NCARRT             PIC 9(9)    BINARY.
05   GS-ECD-NDPBC             PIC 9(9)    BINARY.
05    GS-ECD-LISTNAME             PIC X(20).
05    GS-ECD-VERSION             PIC X(12).
05    GS-ECD-CERTIFICATIONDATE             PIC X(24).
05    GS-ECD-PSEARCHPATH             PIC X(256).
05    GS-ECD-TEMPLATENAME             PIC X(256).
05    GS-ECD-NZ4CHANGED             PIC 9(9)    BINARY.
05    GS-ECD-NLOT             PIC 9(9)    BINARY.
05   GS-ECD-Z4CHANGEVERSION             PIC X(12).
05    GS-ECD-LOTVERSION             PIC X(12).
05    GS-ECD-NHIGHRISEDEFAULT             PIC 9(9) BINARY.
05    GS-ECD-NHIGHRISEEXACT             PIC 9(9) BINARY.
05    GS-ECD-NRURALROUTEDEFAULT             PIC 9(9) BINARY.
05    GS-ECD-NRURALROUTEEXACT             PIC 9(9) BINARY.
05    GS-ECD-NLACS             PIC 9(9) BINARY.
05    GS-ECD-Z4COMPANYNAME             PIC X(40).
05    GS-ECD-LOT-DPCCOMPANYNAME             PIC X(40).
05    GS-ECD-LOT-Z4CONFIG             PIC X(4).
05    GS-ECD-LOT-DPCCONFIG             PIC X(4).
05    GS-ECD-Z4SOFTWARENAME             PIC X(30).
05    GS-ECD-DPCSOFTWARENAME             PIC X(30).
05    GS-ECD-LISTPROCESSORNAME             PIC X(25).
05    GS-ECD-ZIP4DATABASEDATE             PIC 9(9) BINARY.
05    GS-ECD-LOTDATABASEDATE             PIC 9(9) BINARY.
05    GS-ECD-EWS-DENIAL             PIC 9(9) BINARY.
05    GS-ECD-EWS-NTOTALDPV             PIC 9(9) BINARY.
05    GS-ECD-EWS-DPVDATABASEDATE            PIC 9(9) BINARY.

When you specify a version number for either version, Z4ChangeVersion, or LOTVersion, GeoStan updates the corresponding fields in the template cass3553.frm file. For example, entering a version number for Z4ChangeVersion prompts GeoStan to fill these fields on cass3553.frm:

  • B. List, 2b. Date list Processed Z4Change

  • B. List, 3b. Date of Database Product Used Z4Change

  • C. Output, 1b. Total Coded Z4Change Processed.

To develop CASS certified application in GeoStan, you must have the correct license agreement with Precisely. You must also obtain CASS certification from the USPS for every application developed in GeoStan. Using GeoStan does not make an application CASS certified. For information on becoming CASS certified, see Appendix E: CASS certification.

GSZ4CH

Determines if the USPS changed a ZIP + 4 address definition since GeoStan last processed the record.

Syntax

01 GSID          PIC S9(9) BINARY.
01 PZIP          PIC X(USER LEN).
01 PZIP4          PIC X(USER LEN).
01 PDATE          PIX X(USER LEN).
01 GSFUNSTAT         PIC S9(9) BINARY.
*
CALL "GSZ4CH" USING GSID, PZIP, PZIP4, PDATE, GSFUNSTAT.

Arguments

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

PZIP   First five digits of the 9-digit ZIP Code to be tested. Input.

PZIP4   Last four digits of the 9-digit ZIP Code to be tested. Input.

PDATE   Date of the GeoStan ZIP + 4 information file used to process the record. The string’s format is MMYYYY (for example, 081998). Input.

GSFUNSTAT   Return value for the procedure. Output.

Return Values

GS-ERROR   Common reasons for GS-ERROR are:

n The GSL file was not loaded because it was not found in the path.

n The GSL file was not loaded because it was a different release level than the GSD file.

GS-Z4-CHANGE

GS-Z4-NO-CHANGE

Prerequisites

GSINITWP

Notes

For ZIP4CH to work, the GeoStan GSL file must be in a directory listed in the PGPATHS member of GSIINITSTRUCT when calling GSINITWP. The Z4Change file, which is generated by the USPS, contains a record for every ZIP + 4 in the country. Each record contains twelve flags that represent the last twelve months, starting with the current release date. Each of these flags has a value of either True or False, indicating if the ZIP + 4 changed for that monthly postal release. The GeoStan GSL file incorporates this information, which GSZ4Ch references.

Z4Change information is valuable to users who process very large address lists frequently. As you process each record, you can call GSZ4CH and quickly tell if the record needs reprocessing. This information can help you quickly identify only those records that need reprocessing.

Your application must store the date of the GeoStan GSL file used to process a record. GeoStan uses this date as the GSZ4CH PDATE input parameter. This is the same date printed on the GeoStan CD used for record processing, and is one month later that the release date of the USPS files used on the GeoStan CD.

Use the following code example if you are unsure of the release date. You should run this code when standardizing a batch of records and store the resulting date string as input to GSZ4CH in future processing runs.