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