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.