Allows the user to set the properties of the GDLHANDLE.
Syntax
05 GDL-SET-STR.
10 GDL-SS-HANDLE PIC S9(09) BINARY.
10 GDL-SS-TYPE PIC S9(09) BINARY.
10 GDL-SS-DDNAME PIC X(08).
*
CALL "GDLSS"
USING GDL-SET-STR, GDL-RETURN-CODE.
Arguments
GDL-SS-HANDLE
The gdlHandle initialized by GDLINIT (GDL-INIT-HANDLE). Input.
GDL-SS-TYPE
The type of shape to find. Input.
GDL-ZIP5-FILENAME | Name of the gsb file that contains the ZIP Code boundaries. |
GDL-ZIP9-FILENAME | Name of the US.Z9 file of ZIP Code centroids. |
GDL-GEOSTAN-PATH |
Direct GDL to return data in the datum specified in GeoStan. GDL performs datum conversions on the address- and ZIP4-level error surfaces created with GDLGES.This value should be the same as the value used to initialize GeoStan. If this path is not set, GDL returns data in the NAD83 datum. |
GDL-SS-DDNAME
An array of characters from which to read the property value. Input.
size
The size of the character array in value. Input.
Return Values
GDL-OK | Success |
GDL-NOT-FOUND | Did not find a type (GDL-SS-TYPE) |
Prerequisites
GDLINIT
Alternates
None.
Notes
The argument GDL-TEMP-PATHNAME is ignored on MVS.