Deprecated. Initializes GeoStan for DPV.
Syntax
01 GSID PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT PIC S9(9) BINARY.
01 STRUCT-SIZE PIC S9(9) BINARY.
01 W-HAVE-MESSAGE PIC S9(9) BINARY VALUE +0.
01 W-ERROR-MSG PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL PIC X(256) VALUE LOW-VALUES.
*
CALL 'GSDPVINR' USING GSID, GS-DPV-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.
Arguments
GSID ID returned by GSINIT for the current instance of GeoStan. Input.
GS-DPV-INIT-STRUCT Also defined in GEOSTAN.H. This structure contains the following:
GS-DIS-STRUCT-VERSION Set to GS-GEOSTAN-VERSION. Input.
GS-DIS-OPTIONS Reserved for future implementation. Input.
GS-DIS-PDIRECTORY String [GS-MAX-STR-LN] that specifies the directory containing the DPV file. Input.
GS-DIS-SECURITY-KEY Security key to initialize DPV functionality. Input.
GS-DIS-STATUS Indicates the successful initialization of DPV. the following table contains the constants used to test each significant bit. Output.
GS-DPV-FILE-SECURITY |
The DPV security file for initializing the DPV functionality. |
GS-DPV-FILE-ALL |
The DPV data initialized successfully. |
GS-DIS-DATA-ACCESS Indicates the type of files to load and how to access the files. The following table contains the possible values. Input.
DPV-DATA-FULL-FILEIO |
Default. dpvh.db accessed via file I/O and Micro (U) memory model. Use this option for OS/390. |
DPV-DATA-FULL-MEMORY |
dpvh.db loaded completely into memory and Huge (H) memory model (about 1.3 GB). Use this option to gain performance improvement by reducing repetitive file I/O. |
DPV-DATA-SPLIT-FILEIO |
dpvs.db accessed via file I/O and Micro (U) memory model. Separates the DPV data file into multiple smaller files, based on the first 2 digits of the ZIP Code. If you sort your mailing file by ZIP Code, you can bring the relevant portion of the DPV file into memory. This process uses 32 MB of storage, but reduces the number of I/O requests that normally occurs when you use the full DPV data file. Use this option if your file is sorted by ZIP Code and you have limited memory. |
DPV-DATA-SPLIT-MEMORY |
dpvs.db loaded completely into memory and Huge (H) memory model (about 965 MB) |
DPV-DATA-FLAT-FILEIO |
dpv.db accessed via file I/O and Micro (U) memory model. |
DPV-DATA-FLAT-MEMORY |
dpv.db Large (L) memory model (about 70 MB). This configuration will provide the best performance overall. |
GS-DIS-MEMORY-BUFFER-SIZE Number of megabytes used to load buffered files into memory. Input.
This option is only valid if dataAccess!= DPV-DATA-FULL-MEMORY. The following are possible values:
0 |
Default. Do not load DPV files into memory. Access is through file I/o. Note: Use this option for OS/390. |
1-999 |
Number of megabytes to allocate for buffered I/o. |
DPV-DATA-SPLIT-FILEIO |
Use if your file is sorted by ZIP Code and you have limited memory. Uses a split data format that separates the DPV data file into multiple smaller files, based on the first 2 digits of the ZIP Code. If you sort your mailing file by ZIP Code, you can use this value to bring the relevant portion of the DPV file into memory. This process uses 32 MB of storage, but reduces the number ofI/O requests that normally occurs when you use the full DPV data file. |
STRUCT-SIZE The size of the DPVINITSTRUCT data structure. Input.
GSFUNSTAT Return value for the procedure. Output.
Return Values
GS-ERROR Call GSERRGTX for more information
GS-WARNING Call GSERRGTX for more information
Prerequisites
GSINIT
Example
First initialize GeoStan for DPV.
**** WORKING STORAGE VARIABLES ******************
01 GSID PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT PIC S9(9) BINARY.
01 STRUCT-SIZE PIC S9(9) BINARY.
01 W-HAVE-MESSAGE PIC S9(9) BINARY VALUE +0.
01 W-ERROR-MSG PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL PIC X(256) VALUE LOW-VALUES.
COPY GSCONST.
**** SAMPLE CODE TO INITIALIZE DPV **************
**** PLACE AFTER CALL TO GSINIT **************
MOVE '(YOUR DPV LICENSE KEY)' TO GS-DIS-SECURITY-KEY.
MOVE GS-GEOSTAN-VERSION TO GS-DIS-STRUCT-VERSION.
MOVE DPV-DATA-FULL-FILEIO TO GS-DIS-DATA-ACCESS.
MOVE ZERO TO GS-DIS-MEMORY-BUFFER-SIZE.
MOVE GS-DPV-COB-STRUCT-SIZE TO STRUCT-SIZE.
MOVE 'NULL' TO GS-DIS-PDIRECTORY.
MOVE X'00' TO GS-DIS-PDIRECTORY(5:1).
CALL 'GSDPVINR' USING GSID, GS-DPV-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.
IF GSFUNSTAT = GS-SUCCESS
DISPLAY 'DPV INITIALIZED SUCCESSFULLY'
ELSE
DISPLAY '********************************'
DISPLAY 'DPV FAILED TO INITIALIZE'
DISPLAY 'GSFUNSTAT IS:', GSFUNSTAT
DISPLAY 'GSID IS:', GSID
DISPLAY 'GS-DPV-INIT-STRUCT IS:', GS-DPV-INIT-STRUCT
DISPLAY 'STRUCT-SIZE IS:', STRUCT-SIZE
DISPLAY '********************************'
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
PERFORM UNTIL W-HAVE-MESSAGE IS EQUAL TO ZERO
CALL 'GSERRGTX' USING GSID, W-ERROR-MSG, W-ERROR-DETAIL, GSFUNSTAT
DISPLAY 'W-ERROR-MSG:', W-ERROR-MSG
DISPLAY 'W-ERROR-DETAIL:', W-ERROR-DETAIL
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
END-PERFORM.
After you have initialized DPV and called GSSFIND for an address, you can then call GSDATGET and request any of the following output fields, which are included in the copy member GSCONST:
• GS-DPBC |
•GS-DPV-CONFIRM |
•GS-DPV-CMRA |
• GS-DPV-FALSE-POS |
• GS-DPV-FOOTNOTE1 |
• GS-DPV-FOOTNOTE2 |
•GS-DPV-FOOTNOTE3 |
•GS-DPV-FOOTNOTE4 |
•GS-DPV-FOOTNOTE5 |
•GS-DPV-FOOTNOTE6 |