Retrieves additional metadata in the GSB file.
Syntax
01 SPHANDLE PIC S9(9) BINARY.
01 OBJFILEXTRAINFOHEADER.
02 SOURCE PIC X(256).
02 VERSION PIC X(32).
02 DATECREATED PIC X(32).
02 GSBVERSION PIC S9(9) BINARY.
02 DATUM PIC S9(9) BINARY.
01 SPRETCODE PIC S9(9) BINARY.
*
CALL 'SPOHFQX' USING SPHANDLE, OBJFILEXTRAINFOHEADER, SPRETCODE.
Arguments
SPHANDLE The handle returned by SPINIT for the current instance of Spatial+. Input.
OBJFILEXTRAINFOHEADER A pointer to the structure to be filled with the header information. Output.
Return Values
PIP-OK
PIP-ERROR
Prerequisites
SPOFOP
Alternates
None.
Notes
The SPOHFQX function uses OBJFILEXTRAINFOHEADER as a data structure to hold extended information about a file.
Example
The "C" function pipImportInitEx adds the file information listed below, and the
OBJFILEXTRAINFOHEADER is populated as shown below after calling this function:
Field | Description |
02 SOURCE PIC X(256). | User-defined source of this data. |
02 VERSION PIC X(32). | User-defined version of this data. |
02 DATECREATED PIC X(32). | Date string when the GSB was created. |
02 GSBVERSION PIC S9(9) BINARY. | Current GSB version. |
02 DATUM PIC S9(9) BINARY. |
Datum of user data; either DATUM-NAD27 or DATUM-NAD83 |