The GTMATCH program compares your input addresses (house number, street name, etc.) to the street database and returns information on that address, such as place codes, MCD/CCD codes, and latitude/longitudes.
On Windows and UNIX/Linux:
CALL GTMATCH USING
MATCHER-PARAMETERS
On z/OS:
01 DUMMY-PARM1 PIC X(1).
01 DUMMY-PARM2 PIC X(1).
.
.
CALL GTMATCH USING
DUMMY-PARM1
DUMMY-PARM2
MATCHER-PARAMETERS
When you call the GTMATCH program, you pass it pre-defined parameter areas - blocks of memory with data that is used by both your executable program and GTMATCH. These parameter areas must reside in the linkage section of your executable program. The following table describes the GTMATCH parameter areas.
Data Area |
Data Area Name |
Description |
---|---|---|
Control |
Matcher Control Area (MCA) |
600-byte area consisting of data-items (MCA-xxx) that contain matcher control/processing settings. |
Input |
Matcher Input Address (MIA) |
1500-byte area consisting of data-items (MIA-xxx) that contain input information. |
Output |
Matcher Output Area (MOA) |
6092-byte output area consisting of data-items (MOA-xxx) that contain processing results and return codes. |
Audit |
Matcher Audit Area (GTAADT) |
1,520,001-character audit area consisting of data-items (GTAxxx) that contain counters for processing statistics. |
Matcher Control Area
The following table describes the data-items in the Matcher Control Area (MCA), which totals 600 bytes.
Position |
Name |
Length |
Contents |
---|---|---|---|
1 |
MCA-FUNCTION-REQ |
1 |
Matcher control function: B Called from batch process C Return state/county audit stats E Close files; end program O Called from on-line process. NOTE: Any other value is treated as B. |
2 |
MCA-FIRST- LETTER-EXP-OPT |
1 |
First letter expanded option: Y Enable extra processing for bad first letter (missing, wrong, etc.) N No extra processing (default) Note: Any other value is treated as N.
|
3 |
MCA-STREET- CENTROID-OPT |
1 |
Street centroid option: Y Enable matching to a street segment. Returns street segment centroid information. N Normal matching to range only, rather than segment. (default) Note: Any other value is treated as N.
|
4 |
MCA-ADDRESS- RANGE-OPT |
1 |
Address range matching option: Y Enable matching of house range input. N No range input matching. (default) Note: Any other value is treated as N.
|
5 |
Reserved |
1 |
|
6 |
MCA-ALTERNATE- LOOKUP-OPT |
1 |
Alternate lookup option: 1 Street match preferred over firm match. 2 Firm match preferred over street match. 3 Match to address line only. (default) Note: Any other value is treated as 3.
|
7 |
MCA-ADDR- MATCH-MODE |
1 |
Match mode option: 0 Enable 'Exact' address match mode. 1 Enable 'Close' address match mode. (default) 2 Enable 'Relaxed' address match mode. Note: Any other value is treated as 1.
|
8 |
MCA-FALL- BACK-GEOGRAPHIC- |
1 |
Fallback geographic option: Y Find the first city, county, and/or state centroid, then match from the set of possible matches found. N No geographic centroid search. (default) Note: Any other value is treated as N.
|
9 |
MCA-SEARCH-AREA-OPT |
1 |
Search area option: 1 Search entire finance area for a match. (default) 2 Search a given radius but stays in state (this option requires an input radius - see MCA-SEARCH-RADIUS below). Note: Any other value is treated as 1.
|
10-18 |
MCA-SEARCH-RADIUS |
9 |
Expanded search radius (in miles) to apply as the expanded search area when option 2 is selected in MCA-SEARCH-AREA-OPT above. 1-99 Miles - right justified, padded with zeroes to left. 25 miles (default) Note: A space or any non-numeric value is treated as a zero.
|
19 |
MCA-CACHESIZE |
1 |
Relative cache size used in address matching. Controls the amount of memory that is allocated to store temporary street data during address processing. A smaller cache may slow the performance. 0 Smallest memory usage. 1 Middle memory usage. 2 Largest memory usage. (default) Note: Any other value is treated as 2.
|
20 |
MCA-ADDRESS POINT-INTERP- |
1 |
Address point interpolation option (only for use with point level geocoding): Y Enable address point interpolation. N No address point interpolation. (default) Note: Any other value is treated as N.
|
21 |
MCA-BOUNDARY-CONF |
1 |
Boundary confidence option. Indicates if confidence codes for boundary matches should be returned: Y Return boundary confidence levels. N Do not return boundary confidence levels. (default) Note: Any other value is treated as N.
|
22 |
MCA-USER- BOUNDARY-CONF |
1 |
User boundary confidence option. Indicates if confidence codes for user boundary matches should be returned: Y Enable return of user boundary confidence levels. N Do not return user boundary confidence levels. (default) Note: Any other value is treated as N.
|
23 |
MCA-PLACE-CONF |
1 |
Place confidence option. Indicates if confidence codes for place matches should be returned: Y Enable return of place confidence levels. N Do not return place confidence levels. (default) Note: Any other value is treated as N.
|
24 |
MCA-COUSUB-CONF |
1 |
County subdivision confidence option. Indicates if confidence codes for county subdivision matches should be returned: Y Enable return of county subdivision confidence levels. N Do not return county subdivision confidence levels. (default) Note: Any other value is treated as N.
|
25 |
MCA-COUNTY-CONF |
1 |
County confidence option. Indicates if confidence codes for county matches should be returned: Y Enable return of county confidence levels. N Do not return county confidence levels. (default) Note: Any other value is treated as N.
|
26 |
MCA-LAT-LONG-INPUT |
1 |
Latitude/Longitude input option. Indicates if latitude/longitude coordinates will be input rather than address or ZIP code. Y Latitude/longitude coordinates to be used as input. N Address and lastline info to be used as input. (default) Note: Any other value is treated as N.
|
27 |
MCA-GET-MULTIPLE |
1 |
For a multi-match outcome, indicates which match result should be returned; valid values are 1-9 and value should not be greater than MOA-NUM-MULTIPLE. Note: Any non-numeric value will be ignored.
|
28 |
MCA-BOUNDARY- CACHESIZE |
1 |
The relative size of cache used in boundary file matching: 0 No caching 1 Medium-sized cache (default) 2 Large-sized cache 3 Very large-sized cache Note: Any other value is treated as 1.
|
29 |
MCA-ACCEPT-MULTIPLE |
1 |
Indicates whether address information should be returned in a multi-match outcome: Y Accept multiples and return 1st match information in multi-match list N Do not accept multiples and return information. (default) Note: Any other value is treated as N.
|
30-493 |
Reserved |
464 |
|
494 |
MCA-DB-OVERRIDE-SW |
1 |
Overrides the database expiration: X Override an expired database N Do not override an expired database (default) |
495-503 |
MCA-BOUNDARY- BUFFER-DIST |
9 |
Buffer radius, in feet, to apply to the districts in the boundary file. Numeric value (right justified) padded with zeros to left. A space or any non-numeric value is treated as zero. |
504-512 |
MCA-USER-BND- BUFFER-DIST |
9 |
Buffer radius, in feet, to apply to the districts in the user-defined boundary file. Numeric value (right justified) padded with zeros to left. A space or any non-numeric value is treated as zero. |
513 |
MCA-USER- BOUNDARY-MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to the user-defined boundary file: Y Attempt a match N Do not attempt a match (default) Note: Any other value is treated as N.
|
514 |
MCA-PTC-MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to a payroll tax correspondence file: Y Attempt a match N Do not attempt a match (default) Note: Any other value is treated as N.
|
515 |
MCA-AX2-MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to the GeoTAX Auxiliary file: Y Attempt to match to the GeoTAX Auxiliary file (default) N Do not use the GeoTAX Auxiliary file Note: Any other value is treated as Y.
|
516 |
MCA-AUX-MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to the User Auxiliary file: Y Attempt to match to User Auxiliary file (default) N Do not use the User Auxiliary file Note: Any other value is treated as Y.
|
517 |
MCA-STATE-MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to the state files: Y Attempt to match to state files N Do not use state files (default) Note: Any other value is treated as N.
|
518 |
MCA-STATE-ORDER-OPT |
1 |
Indicates which state file GeoTAX should use to attempt a match and, in the case of both, what the order of searching should be: A Use only the Florida-native formatted file (default) B Use only the TS-158 formatted file C Use both formats and search Florida-native first D Use both formats and search TS-158 first Note: Any other value is treated as
A. Valid checking is done only when state
matching is on.
|
519 |
MCA-BOUNDARY- MATCH-OPT |
1 |
Indicates if GeoTAX should attempt a match to a boundary file, and to which file it should attempt the match: S Attempt a match to the Special Purpose Tax District file I Attempt a match to the Insurance Premium District file R Attempt a match to the Payroll Tax District file N No, do not call (default). Note: Any other value is treated as N.
|
520-527 |
MCA-IO-MODULE-NAME |
8 |
Generic I/O routine name to call. If blank, GeoTAX utilizes I/O routines provided with the product. Program names may differ according to platform. |
528 |
MCA-FL-RELAX-SEC-OPT |
1 |
Indicates if GeoTAX enables matching to the Florida state file without requiring a match on secondary: Y Relax secondary matching N Do not relax secondary matching (default) Note: Any other value is treated as
N.
|
529 |
MCA-LL-SQUEEZE-OPT |
1 |
Indicates if GeoTAX enables a Lat/Lon squeeze: Y Apply squeeze to Lat/Lon (default) N Do not apply squeeze Note: Any other value is treated as
Y.
|
530-534 |
Reserved |
5 |
|
535 |
MCA-TAXRATE- MATCH-OPT |
1 |
Tax Rate matching indicator field. Indicates whether to enable tax rate matching and the type of tax rate to return: G Enable tax rate matching and return general rates. A Enable tax rate matching and return automotive rates. M Enable tax rate matching and return medical rates. C Enable tax rate matching and return construction rates. N Disable tax rate matching (default) Note: Any other value returns zeros in the tax rate output
fields.
|
536 |
MCA-STREET-MATCH-OPT |
1 |
Street match indicator field: Y Use the street matcher (default) N Do not use the street matcher Note: Any other value is treated as
Y.
|
537 |
MCA-CASE |
1 |
Indicates if name fields are in mixed case: Y Yes N No (default) Note: Any other value is treated as
N.
|
538-542 |
Reserved |
5 |
|
543 |
MCA-GTX |
1 |
Indicate if GeoTAX should determine the GeoTAX key: T Attempt to determine information associated with GeoTAX Sovos application. V Return the key using the Precisely Vertex file. N Do not attempt to determine information associated with GeoTAX application. Note: Any other value is treated as
N.
|
544 |
MCA-LATLONG-ALT-FMT |
1 |
Indicates latitude/longitude alternate format. Value supplied will be used to calculate the offset for the street segment. A 090000000N180000000W (default) B 090.000000N180.000000W C 90.000000-180.000000 D 90000000-180000000 Note: Any other value is treated as
A.
|
545 |
MCA-LATLONG-OFFSET |
1 |
Latitude/longitude offset field for the street segment. Value supplied will be used to calculate the offset for the street segment. A No offsetting B 20 feet offset from street segment C 40 feet offset from street segment (default) D 60 feet offset from street segment. Note: Any other value is treated as
C.
|
546-600 |
Reserved |
55 |
|
Matcher Input Area (MIA)
The following table describes the data-items in the Matcher Input Area (MIA), which totals 1500 bytes.
Position |
Name |
Length |
Contents |
---|---|---|---|
1-9 |
MIA-ZIP9 |
9 |
Input ZIP+4 Code to match against the database. |
10-22 |
Reserved |
13 |
|
23-72 |
MIA-CITY |
50 |
Input city name. |
73-122 |
MIA-STATE |
50 |
Input state name. |
123-422 |
MIA-STREETS |
300 |
Input address lines 1, 2, and 3, each 100 bytes long. |
423-722 |
MIA-ADR-BLK |
300 |
Input address block, consisting of: firm name & address lines, each 100 bytes long. If country, ZIP/postal code, city, or state input fields are blank or invalid, this area is searched for those values. |
723-1322 |
Reserved |
600 |
|
1323-1344 |
MIA-LAT-LONG |
22 |
Input latitude (11 bytes) and longitude (11 bytes). The required format for the input coordinates is as follows: Latitude:00.000000 or without the decimal point 00000000 Longitude:000.000000 or without the decimal point 000000000; or 00.000000 or without the decimal point 00000000 |
1345-1416 |
MIA-LIC-FILE-PATH |
72 |
License file path and name. |
1417-1424 |
MIA-LIC-PASSWORD |
8 |
License file password. |
1425-1500 |
Reserved |
76 |
|
Matcher Output Area (MOA)
The following table describes the data-items in the Matcher Output Area (MOA), which totals 6092 bytes.
Position |
Name |
Length |
Contents |
---|---|---|---|
1-2 |
MOA-ABEND-RC |
2 |
Return code from matcher abnormal termination. The first character indicates the file (or set of files affected. Blank Matcher terminated normally A User Auxiliary file problem CE cousub.txb file problem CI Confidence engine problem D Boundary file problem F User Boundary file problem G Address Matching engine problem L Licensing problem S State file problem U GeoTAX Auxiliary file problem X Combination of street and state file problem Z zip.gsb file problem The second position is: E Fatal issue, program terminating F Expired database I Informational |
3-82 |
MOA-ABEND-TXT |
80 |
Text description of matcher abnormal termination; blank if matcher terminated normally. |
83-84 |
MOA-WARN-RC |
2 |
Warning return code; blank if no warnings issued. A return of WN indicates a database will expire next month. |
85-164 |
MOA-WARN-TXT |
80 |
Text description of warning. |
165-194 |
MOA-DESCRIPTION |
30 |
Matching software description. |
195-202 |
MOA-RELEASE-MOD-NUM |
8 |
Matching software release number and modification level. |
203-222 |
MOA-TAXRATE-VINTAGE |
20 |
Precisely Sales and Use Tax Rate file vintage. |
223-262 |
MOA-TAXRATE-VERSION |
40 |
Precisely Sales and Use Tax Rate file version. |
263-382 |
Reserved |
120 |
|
383-402 |
MOA-GEOTAX-VINTAGE |
20 |
Cross-Reference file vintage. |
403-406 |
MOA-GEOTAX-VERSION |
4 |
Cross-Reference file software version. |
407 |
MOA-ST-IND |
1 |
Indicates if the match results are from the Florida State files: F Match to Florida State files. |
408-415 |
MOA-ST-VINTAGE |
8 |
Date the state-supplied file was created, in the formatMM/DD/YY. |
416-423 |
MOA-ST-VERSION |
8 |
Version of the GeoTAX master file that created the State-supplied files, in the format Rnn.nMnn. |
424-432 |
Reserved |
9 |
|
433 |
MOA-GRC |
1 |
General return codes: 5 ZIP Code match 9 ZIP+4 Code match A User Auxiliary file match C Street Centroid match F Fallback Geographic match G State-supplied file match I Intersection match L Landmark Auxiliary file match M Multiple match (multi-match) O Input Latitude/Longitude coordinates match P Address point match S Street address match U GeoTAX Auxiliary file match X Aborted processing or expired database blank Did not match Note: GeoTAX attempts matches to files in the following order:
Landmark Auxiliary File, User Auxiliary File, state-supplied
file, GeoTAX Auxiliary file, Points file, then Streets
file.
|
434 |
MOA-STREET-O-RC |
1 |
For street address matching, the output street address return code: Z ZIP Code not found in street address database S Street not found in ZIP Code H House number not found on street L Lat/long not determined on the GeoTAX Auxiliary file, the User Auxiliary file, or the state-supplied file blank Successful match |
435-442 |
Reserved |
8 |
|
443-444 |
MOA-STATE-CODE |
2 |
FIPS State code. |
445-447 |
MOA-COUNTY-CODE |
3 |
FIPS County code. |
448-453 |
MOA-CENSUS-TRACT |
6 |
Census tract code. |
454 |
MOA-BLOCK-GROUP |
1 |
Census block group. |
455-456 |
MOA-STATE-ABBREVIATION |
2 |
State abbreviation. |
457-481 |
MOA-COUNTY-NAME |
25 |
County name. |
482-535 |
Reserved |
54 |
|
536-540 |
MOA-MCDCCD-CODE |
5 |
Minor Civil Division/Census County Division (MCD/CCD) Code. |
541-580 |
MOA-MCDCCD-NAME |
40 |
MCD/CCD name. |
581-585 |
MOA-PLACE-CODE |
5 |
Place code. |
586-625 |
MOA-PLACE-NAME |
40 |
Place name. |
626-627 |
MOA-PLACE-CLASS-CODE |
2 |
Place class code. |
628 |
MOA-PLACE-INCORP-FLAG |
1 |
Place incorporated/unincorporated flag: 1 Place code returned is incorporated 0 Place code returned is unincorporated blank Place code is not found or does not exist on the FIPS 55 Place Code roster. |
629-635 |
MOA-PLACE-LAST- ANNEXED |
7 |
Last Annexed Date (in MM/YYYY format). This date represents the month and year of the most recent boundary change or the most recent available boundary information. This field is never blank |
636-642 |
MOA-PLACE-LAST- UPDATED |
7 |
Last Updated Date (in MM/YYYY format). This date reflects the month and year when TeleAtlas updated the database to reflect attribute (name change, FIPS change, incorporated/unincorporated change, etc.) or boundary edits to the Place. |
643-649 |
MOA-PLACE-LAST- VERIFIED |
7 |
Last Verified Date (in MM/YYYY format). The Last Verified date is the month and year that TeleAtlas verified municipality change information. |
650-658 |
MOA-PLACE-GNIS |
9 |
Unique Geographic Names Information System (GNIS) code. |
659 |
MOA-GEOTAX-RC |
1 |
GeoTAX return code denoting the level of match obtained against the PB Vertex or Sovos cross-reference files: E Exact match, using all 5 fields P Partial match, using 4 fields A Alternate match, using 3 fields N Record is default-coded based on valid state code Blank No matching GeoTAX record found. |
660-668 |
MOA-GEOTAX-KEY |
9 |
9-byte key. For PB Vertex cross-reference file: ā¢2-byte Vertex state code, 3-byte FIPS county code, 4-byte Vertex city code For Sovos cross-reference files: ā¢Sovos SUT - 2-byte SUT state code, 5-byte ZIP Code, 2-byte SUT geocode ā¢Sovos TWE - variable-length TWE geocode |
669 |
Reserved |
1 |
|
670-672 |
MOA-BLOCK-ID |
3 |
Census Block ID |
673-689 |
Reserved |
17 |
|
690 |
MOA-LATLONG-LEVEL |
1 |
The latitude/longitude coordinates may be returned from one of a number of possible sources, some of which are optional. The output latitude/longitude level return code is a single character denoting the level for which the geocode was determined, as follows: 2 ZIP+2 Code centroid 4 ZIP+4 Code centroid B Block group centroid C City centroid L Landmark Auxiliary file O Latitude/longitude was matched as input R Street latitude/longitude based on street address S State centroid T Census tract centroid U GeoTAX Auxiliary file Z ZIP Code centroid blank Could not determine latitude/longitude. If the General Return Code (MOA-GRC) is "P" (point match), then the following are possible values and have the following meaning: 0 Latitude/longitude coordinates from User Dictionary. 2 Latitude/longitude coordinates from Parcel Centroid. 4 Latitude/longitude coordinates from Address Point. 5 Latitude/longitude coordinates from Structure Centroid. 7 Latitude/longitude coordinates from Manually-placed Point. 8 Latitude/longitude coordinates from Front Door Point. 9 Latitude/longitude coordinates from Driveway Offset Point. A Latitude/longitude coordinates from Street Access Point. B Latitude/longitude coordinates from Base Parcel Point. C Latitude/longitude coordinates from Backfill Address Point. D Latitude/longitude coordinates from Virtual Address Point. E Latitude/longitude coordinates from Interpolated Address Point. |
691-698 |
MOA-LATITUDE |
8 |
Latitude ā 7-digit number followed by a 1-character directional. The 7-digit number is in degrees and calculated to 4 decimal places (decimal is implied, not shown). The 1-character directional is one of the following: N North S South. |
699-706 |
MOA-LONGITUDE |
8 |
Longitude ā A 7-digit number followed by a 1-character directional. The 7-digit number is in degrees and calculated to 4 decimal places (decimal is implied, not shown). The 1-character directional is one of the following: E East W West. |
707-736 |
MOA-LAT-LONG-ALT-1 |
30 |
Indicates the latitude/longitude alternate formats: A 090000000N180000000W (default) B 090.000000N180.000000W C 90.000000-180.000000 D 90000000-180000000 |
737-756 |
MOA-LAT-LONG-ALT2 |
20 |
Used to output latitude and longitude in a format used by the ARCOUT parameter.
|
757-766 |
Reserved |
10 |
|
767-1066 |
MOA-AUX-AREA |
300 |
Reserved for data retrieved as a result of a GeoTAX Auxiliary or User Auxiliary match containing positionsxx-xxx from the corresponding G1GTAX2 or G1GTAUX record area. |
1067-1266 |
MOA-STATE-SUPPLIED-AREA |
200 |
Reserved for data retrieved as a result of a state-supplied file match. Each format supported contains its own mask of what data resides in this location. Currently, these formats are the Florida-native format and the TS-158 format. For more information, see STEOUT . |
1267-1276 |
Reserved |
10 |
|
1277 |
MOA-TS-IND |
1 |
Indicates if the match results are from the TS-158 State files: N Match to TS-158 State files. |
1278-1285 |
MOA-TS-VINTAGE |
8 |
Vintage of the state-supplied file. |
1286-1293 |
MOA-TS-VERSION |
8 |
Software version of the state-supplied file. |
1294-1295 |
MOA-BOUNDARY- NUM-OF-SPD |
2 |
Number of Special Purpose Tax Districts (SPDs) returned from boundary match call. |
NOTE: The following data (for positions 1296-2675 occurs in 10 blocks of 138 bytes each, the contents of which vary depending on the boundary file used. |
|||
1296-2675 |
MOA-TAX-DIST-CODE |
3 |
Tax District Code. |
|
MOA-TAX-DIST-NUM |
5 |
Tax District Number. |
|
MOA-TAX-DIST-TYPE |
6 |
Tax District Type. Note: See Type Codes for more information regarding state and
type codes.
|
|
MOA-TAX-DIST-ID |
10 |
Tax District ID. |
|
MOA-TAX-DIST-ST-SPD-CODE |
|
State Supplied Special District Code. Note: MOA-TAX-DIST-ST-SPD-CODE is for SPD file return only.
|
|
MOA-TAX-DIST-IDSUPP |
10 |
Supplemental Tax District ID (Jurisdiction ID). |
|
MOA-TAX-DIST-NAME |
60 |
Tax District name. |
|
MOA-TAX-DIST-FLAG |
10 |
Tax District flag. |
|
MOA-TAX-DIST-VER-DATE |
6 |
Tax District version date. |
|
MOA-TAX-DIST-EFF-DATE |
6 |
Tax District effective date. |
|
MOA-TAX-DIST-CMP-DATE |
6 |
Tax District compiled date. |
|
MOA-TAX-DIST-UPD-DATE |
6 |
Tax District update date. |
|
MOA-TAX-DIST-BUFFER-RC |
1 |
Status of the buffered point: P Point in the polygon I Point in the buffer inside the polygon B Point in the buffer, outside of the polygon blank Polygon not found. |
|
MOA-TAX-DIST-DISTANCE |
9 |
Distance, in feet, from the tax district border. |
2676-2677 |
MOA-BOUNDARY-NUM-OF-USR |
2 |
Number of user-defined boundaries; up to 10. |
NOTE: The following data (for positions 2678-3477) occurs in10 blocks of 80 bytes each; 1 block for each district in the user-defined boundary file. |
|||
|
MOA-USR-DIST-ID |
10 |
User-defined input field. |
|
MOA-USR-DIST-SUPP |
10 |
User-defined input field. |
|
MOA-USR-DIST-DESC |
50 |
Description of the district. |
|
MOA-USR-DIST-BUFFER-RC |
1 |
Status of the buffered point as the first byte: P Point in the polygon I Point in the buffer inside the polygon B Point in the buffer, outside of the polygon Distance to the border for the remaining 9 bytes. |
|
MOA-USR-DIST-DISTANCE |
9 |
Distance, in feet, from the tax district border. |
3478 |
MOA-PTC-GRC |
1 |
Type of match found: P District ID G GNIS Code F County FIPS Code S State FIPS Code |
3479 |
MOA-PTC-CODE-CNT |
1 |
Number of PTC codes found. |
3480-3511 |
MOA-PTC-STCO-NAME |
32 |
State abbreviation and county name. |
NOTE: The following data (for positions 3512-3841) occurs in 6 blocks of 55 bytes each. |
|||
|
MOA-PTC-CODE |
15 |
Payroll code. |
|
MOAT-PTC-DESC |
40 |
Payroll description. |
3842-3847 |
MOA-PTC-FLAGS |
6 |
Indicates if the payroll file is used for a match: Y Used N Not used (default) |
3848-3867 |
MOA-PTC-VINTAGE |
20 |
Software vintage of the payroll file. |
3868-3875 |
MOA-PTC-VERSION |
8 |
Software version of the payroll file. |
3876-3895 |
MOA-BOUNDARY-VINTAGE |
20 |
Software vintage of the SPD file. Only used with files newer than November 2007. |
Note: The following data (for positions 3896-4755) occurs in 10
blocks of 86 bytes each; 1 block for each district in the
Insurance Premium boundary file.
|
|||
3896-4755 |
MOA-TAX-DIST-IPD-EXT-NOTES |
20 |
Kentucky Tax Code descriptions |
|
MOA-TAX-DIST-IPD-EXT-CHGDT |
6 |
MMDDYY - Date of any type of change the row made by the editing team |
|
MOA-TAX-DIST-IPD-EXT-EFFDT |
6 |
MMDDYY- Identifies when district becomes active - State supplied |
|
MOA-TAX-DIST-IPD-EXT-EXPDT |
6 |
MMDDYY - Identifies when district becomes inactive - State supplied |
Note: The following data occurs in 8 blocks of 6 bytes each; 1 block
for each type of insurance.
|
|||
|
MOA-TAX-DIST-IPD-EXT-RTE |
5 |
Format is dependent on associated flag |
|
MOA-TAX-DIST-IPD-EXT-RTEFMT |
1 |
P Percentage: .1 = 10%, .0575 = 5.75% F Flat Fee dollar amount: 15.00 M Multiple Percentages has a semi colon as a delimiter: 3;7 = "3% or 7%" |
4756-4908 |
Reserved |
153 |
|
Spatial returns for place and cousub (20 bytes) |
|||
4909 |
MOA-PLACE-BUFFER-RC |
1 |
Status of the buffered point: P Point in the polygon I Point in the buffer inside the polygon B Point in the buffer, outside of the polygon blank Polygon not found. |
4910-4918 |
MOA-PLACE-DISTANCE |
9 |
Distance, in feet, from the place district border. |
4919 |
MOA-COUSUB-BUFFER-RC |
1 |
Status of the buffered point: P Point in the polygon I Point in the buffer inside the polygon B Point in the buffer, outside of the polygon blank Polygon not found. |
4920-4928 |
MOA-COUSUB-DISTANCE |
9 |
Distance, in feet, from the county subdivision district border. |
Confidence code returns (71 bytes) |
|||
4929-4930 |
MOA-SURFACE-TYPE |
2 |
Confidence Surface types: 0 Undefined 1 The search failed - address was not found 2 Intersection confidence-surface generated 3 Interpolated street segment 4 Point level match 5 State confidence-surface generated 6 County confidence-surface generated 7 City confidence-surface generated 8 Reserved 9 A ZIP Code confidence-surface generated 10 A ZIP+2 confidence-surface generated 11 A ZIP+4 confidence-surface generated 12 Reserved 13 A street centroid confidence-surface generated |
4931-4933 |
MOA-CONF-PLACE |
3 |
The returned confidence code for a place. |
4934-4936 |
MOA-CONF-COUSUB |
3 |
The returned confidence code for a county subdivision. |
4937-4939 |
MOA-CONF-COUNTY |
3 |
The returned confidence code for a county. |
4940-4969 |
MOA-CONF-BND |
3 |
The returned confidence code for a comparison to a boundary file. Data occurs in 10 blocks of 3 bytes each. |
4970-4999 |
MOA-CONF-USER-BND |
3 |
The returned confidence code for a comparison to a user-defined boundary file. Data occurs in 10 blocks of 3 bytes each. |
5000 |
Reserved |
1 |
|
Address matching return codes & data |
|||
5001-5004 |
MOA-ADDR-MATCH-CODE |
4 |
The returned Match Code indicates the portions of the address that matched or did not match to the reference file. For values, see Match codes. |
5005-5008 |
MOA-ADDR-LOC-CODE |
4 |
The returned Location Code indicates the methodology used to compute the geocode and may also provide information about the accuracy of the assigned geocode. For values, see Location codes. |
5009-5028 |
MOA-ADDR-DB-VERSION |
20 |
Address Matcher database version. |
5029-5068 |
MOA-ADDR-SW-VERSION |
40 |
Address Matcher software version. |
5069-5108 |
MOA-ADDR-FIRM-NAME |
40 |
Output Firm name |
5109-5168 |
MOA-ADDR-ADDRESS-LINE-1 |
60 |
Output Address Line 1. |
5169-5228 |
MOA-ADDR-ADDRESS-LINE-2 |
60 |
Output Address Line 2. |
5229-5288 |
MOA-ADDR-LAST-LINE |
60 |
Output Address Last Line. |
5289-5318 |
MOA-ADDR-URB |
30 |
Output urbanization name. |
5319-5346 |
MOA-ADDR-CITY |
28 |
Output city. |
5347-5348 |
MOA-ADDR-STATE-ABBREV |
2 |
Output state abbreviation. |
5349-5353 |
MOA-ADDR-ZIP |
5 |
Output ZIP Code. |
5354-5357 |
MOA-ADDR-ZIP4 |
4 |
Output 4 character add-on code for ZIP+4 Code. |
5358-5368 |
MOA-ADDR-HOUSE-NUM |
11 |
Output house number. |
5369-5370 |
MOA-ADDR-PRE-DIR |
2 |
Output pre-directional. |
5371-5410 |
MOA-ADDR-STREET-NAME |
40 |
Output street name. |
5411-5414 |
MOA-ADDR-STREET-TYPE |
4 |
Output street type. |
5415-5416 |
MOA-ADDR-POST-DIR |
2 |
Output post-directional. |
5417-5420 |
MOA-ADDR-UNIT-TYPE |
4 |
Output secondary type (e.g. Apt., Suite) |
5421-5431 |
MOA-ADDR-UNIT-NUM |
11 |
Output secondary number. |
5432-5436 |
MOA-CBSA-CODE |
5 |
CBSA code. |
5437-5511 |
MOA-CBSA-NAME |
75 |
CBSA name. |
5512-5516 |
MOA-CBSAD-CODE |
5 |
CBSA Division code. |
5517-5588 |
MOA-CBSAD-NAME |
72 |
CBSA Division name. |
5589-5591 |
MOA-CSA-CODE |
3 |
CSA code. |
5592-5668 |
MOA-CSA-NAME |
77 |
CSA name. |
5669 |
MOA-METRO-FLAG |
1 |
Metropolitan flag. Indicates if the CBSA is a "Metropolitan Statistical Area" or a "Micropolitan Statistical Area". Y Metropolitan statistical area N Micropolitan statistical area |
5670 |
MOA-NUM-MULTIPLE |
1 |
The number of multiple matches found for a given input address. |
5671-5672 |
MOA-ADDR-DATA-TYPE |
2 |
Data type of address match: 0 USPS 1 TIGER 2 TomTom Street 6 NAVTEQ Street 7 TomTom Point 8 Centrus Point 11 NAVTEQ Point 12 Master Location Data 90 State-supplied file 91 User Auxiliary file 92 Landmark Auxiliary file 93 GeoTAX Auxiliary file |
5673-5685 |
MOA-ADDR-PB-KEY |
13 |
The PreciselyID unique identifer is returned when a match is made to the Master Location Dataset (MLD). This field is a persistent identifier for an address. The PreciselyID unique identifier serves as a lookup key with Precisely GeoEnrichment datasets to add attribute data for an address location. The leading character is a 'P'. For example, P00001XSF1IF. |
5686-5799 |
Reserved |
114 |
|
Precisely Sales & Use Tax Rate data Rate value format is 0.00000000 |
|||
5800 |
MOA-TAXRATE-GRC |
1 |
Tax Rate return code denoting the level of match obtained against the Precisely Sales and Use Tax Rate table: E Exact match, using all 5 fields P Partial match, using 4 fields A Alternate match, using 3 fields N Record is default-coded based on valid state code Blank No matching Precisely Sales and Use Tax Rate record found. |
5801-5810 |
MOA-TAXRATE-SALES-COMBINED |
10 |
The sum of the state, county, municipality and SPD sales tax rates. |
5811-5820 |
MOA-TAXRATE-SALES-STATE |
10 |
State sales tax rate. |
5821-5830 |
MOA-TAXRATE-SALES-COUNTY |
10 |
County sales tax rate. |
5831-5840 |
MOA-TAXRATE-SALES-MUNI |
10 |
Municipality sales tax rate. |
5841-5940 |
MOA-TAXRATE-SALES-SPD |
10 |
SPD 1-10 sales tax rates. Data occurs in 10 blocks of 10 bytes each. |
5941-5950 |
MOA-TAXRATE-USE-COMBINED |
10 |
The sum of the state, county, municipality and SPD use tax rates. |
5951-5960 |
MOA-TAXRATE-USE-STATE |
10 |
State use tax rate. |
5961-5970 |
MOA-TAXRATE-USE-COUNTY |
10 |
County use tax rate. |
5972-5980 |
MOA-TAXRATE-USE-MUNI |
10 |
Municipality use tax rate. |
5981-6080 |
MOA-TAXRATE-USE-SPD |
10 |
SPD 1-10 use tax rates. Data occurs in 10 blocks of 10 bytes each. |
6081-6092 |
Reserved |
12 |
|
Matcher Audit Area (GTAADT)
The audit area is primarily a series of counters indicating the number of database file matches, by county and state, for each of the logical database files. The first time your COBOL program calls GTMATCH, GTAADT initializes this counting area to zero. For subsequent calls, GTMATCH increments these fields individually. The following table describes the subfields in the Matcher Audit (GTAADT) parameter area, which totals 1,520,001 bytes.
Position |
Name |
Length |
Contents |
---|---|---|---|
1 |
GTAA-FUNCTION-REQ |
1 |
Function. |
Note: The following occurs 4000 times, one for each county in the
country (total of 1,320,000 bytes).
|
|||
|
GTAA-CNTY-NAME |
20 |
County name. |
|
GTAA-PROC |
5 |
Count of records processed. |
|
GTAA-MAT-A |
5 |
Count of User Auxiliary file matches. |
|
GTAA-MAT-U |
5 |
Count of GeoTAX Auxiliary file matches |
|
GTAA-MAT-ST |
5 |
Count of state-level matches. |
|
GTAA-MAT-L |
5 |
Count of Landmark Auxiliary matches |
|
GTAA-MAT-P |
5 |
Count of Point matches. |
|
GTAA-MAT-I |
5 |
Count of Intersection matches. |
|
GTAA-MAT-S |
5 |
Count of street-level matches. |
|
GTAA-MAT-C |
5 |
Count of Street Centroid matches. |
|
GTAA-MAT-9 |
5 |
Count of ZIP+4-level matches. |
|
GTAA-MAT-5 |
5 |
Count of ZIP Code-level matches. |
|
GTAA-MAT-F |
5 |
Count of Fallback Geocoding matches. |
|
GTAA-MAT-M |
5 |
Count of Multiple matches. |
|
GTAA-TRK-NO |
5 |
Census Tract no-match counts |
|
GTAA-TRK |
5 |
Census Tract matched counts. |
|
GTAA-BLK-NO |
5 |
Block Group no-match counts |
|
GTAA-BLK |
5 |
Block Group matched counts. |
|
GTAA-SPD |
5 |
Count of locations contained in an SPD/IPD/PAY. |
|
GTAA-SPD-1 |
5 |
Count of locations in one SPD/IPD/PAY. |
|
GTAA-SPD-2 |
5 |
Count of locations in two SPD/IPD/PAYs |
|
GTAA-SPD-34 |
5 |
Count of locations in three or four SPD/IPD/PAYs. |
|
GTAA-SPD-5 |
5 |
Count of locations in more than four SPD/IPD/PAYs. |
|
GTAA-USR |
5 |
Count of locations contained in a user district. |
|
GTAA-USR-1 |
5 |
Count of locations in one user district |
|
GTAA-USR-2 |
5 |
Count of locations in two user districts. |
|
GTAA-USR-3P |
5 |
Count of locations in three or more user districts. |
|
GTAA-MCD-NO |
5 |
MCD/CCD Code no-match counts. |
|
GTAA-MCD- |
5 |
MCD/CCD Code matched counts. |
|
GTAA-MCD-NM |
5 |
MCD/CCD name matched counts. |
|
GTAA-PLC-NO |
5 |
Place Code no-match counts. |
|
GTAA-PLC |
5 |
Place Code matched counts. |
|
GTAA-PLC-NM |
5 |
Place name matched counts. |
|
GTAA-PLC-A |
5 |
Place annexed date matched counts. |
|
GTAA-PLC-V |
5 |
Place verified date matched counts. |
|
GTAA-PLC-U |
5 |
Place updated date matched counts. |
|
GTAA-PLC-CC |
5 |
Place class code matched counts. |
|
GTAA-PLC-I |
5 |
Place incorporated status matched counts. |
|
GTAA-PLC-UI |
5 |
Place unincorporated status matched counts. |
|
GTAA-XRF-TRY |
5 |
GeoTAX cross-reference file match attempts. |
|
GTAA-XRF |
5 |
GeoTAX cross-reference file matches. |
|
GTAA-XRF-NO |
5 |
GeoTAX cross-reference file no-matches. |
|
GTAA-XRF-E |
5 |
GeoTAX cross-reference file exact matches using all 5 input parameters (state/county/place/ZIP code/place name). |
|
GTAA-XRF-P |
5 |
GeoTAX cross-reference file Partial matches using the first 4 input fields (state/county/place/ZIP code). |
|
GTAA-XRF-A |
5 |
GeoTAX cross-reference file Alternate matches using postal/place name-based answer (ZIP Code/place name). |
|
GTAA-XRF-N |
5 |
GeoTAX cross-reference file unsuccessful matches, default coded with table-based state code lookup. |
|
GTAA-PTC-TRY |
5 |
PTC file match attempts. |
|
GTAA-PTC |
5 |
PTC file matches. |
|
GTAA-PTC-NO |
5 |
PTC file no-matches. |
|
GTAA-LL-NO |
5 |
Lat/long no-match counts. |
|
GTAA-LL |
5 |
Lat/long matched counts. |
|
GTAA-LL-L |
5 |
Lat/Long Landmark Auxiliary level matched counts. |
|
GTAA-LL-P |
5 |
Lat/Long Point level matched counts. |
|
GTAA-LL-I |
5 |
Lat/Long Intersection level matched counts. |
|
GTAA-LL-R |
5 |
Lat/long address level matched counts. |
|
GTAA-LL-U |
5 |
Lat/long GeoTAX Auxiliary level matched counts. |
|
GTAA-LL-4 |
5 |
Lat/long ZIP+4 Code centroid matched counts. |
|
GTAA-LL-B |
5 |
Lat/long Block group centroid matched counts. |
|
GTAA-LL-2 |
5 |
Lat/long ZIP+2 Code centroid matched counts. |
|
GTAA-LL-T |
5 |
Lat/long Census tract centroid matched counts. |
|
GTAA-LL-Z |
5 |
Lat/long ZIP Code centroid matched counts. |
|
GTAA-LL-C |
5 |
Lat/Long City Centroid level matched counts. |
|
GTAA-LL-S |
5 |
Lat/Long State Centroid level matched counts. |
1,320,002-1,520,001 |
GTAA-IDX-GRP |
200,000 |
Index Group. |
The next row describes the contents of GTAA-IDX-GRP. Occurs 100,000 times. |
|||
|
GTAA-IDX-VAL |
2 |
The value for the different state/county combinations. |