Creates a shape of a given type with specified coordinates.
Syntax
05 GDL-SHAPE-CREATE.
10 GDL-SC-HANDLE PIC S9(09) BINARY.
10 GDL-SC-SHAPE PIC S9(09) BINARY.
10 GDL-SC-NAME PIC X(80).
10 GDL-SC-TYPE PIC S9(09) BINARY.
10 GDL-SC-X-POINT COMP-2.
10 GDL-SC-Y-POINT COMP-2.
10 GDL-SC-POINTS-PER-PART PIC S9(09) BINARY.
10 GDL-SC-PART-COUNT PIC S9(09) BINARY.
*
CALL "GDLSC"
USING GDL-SHAPE-CREATE, GDL-RETURN-CODE.
Arguments
GDL-SC-HANDLE
The gdlHandle initialized by GDLINIT (GDL-INIT- HANDLE). Input.
GDL-SC-SHAPE
A pointer to the new gdlShape object. Output.
GDL-SC-NAME
The name of the object being created. Input.
GDL-SC-TYPE
The type of shape to create. Input.
Type options:
GDL-POINT |
GDL-LINE |
GDL-POLYGON |
GDL-SC-X-POINT
An array of x coordinates in decimal degrees. Input.
GDL-SC-Y-POINT
An array of y coordinates in decimal degrees. Input.
GDL-SC-POINTS-PER-PART
An array of integers indicating the number of points in each part. Input.
GDL-SC-PART-COUNT
The number of parts. Input.
Return Values
GDL-OK | Success |
GDL-ERROR | An internal error occurred |
GDL-WRONG-TYPE | Type setting is not one of the allowed values or the type is inconsistent |
Prerequisites
GDLINIT
Alternates
None.
Notes
Following instances of this procedure, you should call GDLSF with the output shape when you are finished using the output shape to release system resources.