Deprecated. Controls the matching mode used by GSSFIND.
Syntax
01 GSID PIC S9(9) BINARY.
01 MATCH-MODE PIC 9(4) BINARY.
01 GSFUNSTAT PIC 9(4) BINARY.
*
CALL "GSSMM" USING GSID, MATCH-MODE, GSFUNSTAT.
Arguments
GSID ID returned by GSINIT for the current instance of GeoStan. Input.
MATCH-MODE Variable value indicating match mode type. The following table contains the valid variables. Input.
GS-MODE-EXACT |
Requires an exact name match. Generates the fewest number of possibles to search. |
GS-MODE-CLOSE |
Default. Requires a very close name match. Generates a moderate number of possibles to search |
GS-MODE-RELAX |
Requires a close name match. Generates the largest number of possibles to search. |
GS-MODE-CASS |
Requires a close name match. Generates the largest number of possibles to search. This setting imposes additional rules to ensure compliance with the USPS regulations for CASS software. For example, this mode disables intersection matching, and matching to the street network file for standardization. |
GSFUNSTAT Contains the return value for the procedure. Output.
Return Values
Old match mode, or a -1 if the new match mode entered is invalid.
Prerequisites
GSINIT
or GSCLEAR
Notes
GSSMM affects how GSDATSET performs. For this reason, call this procedure only immediately after GSINIT, or after a GSCLEAR. If you call this procedure after loading data with GSDATSET, the results are undefined.