Retrieves current error information.
Syntax
01 GSID PIC S9(9) BINARY.
01 GSFUNSTAT PIC S9(9) BINARY.
01 MESSAGE-STRING PIC X(256).
01 DETAIL-STRING PIC X(256).
*
CALL "GSERRGET" USING GSID, MESSAGE-STRING, DETAIL-STRING, GSFUNSTAT.
Arguments
GSID ID returned by GSINITWP for the current instance of GeoStan. Input.
GSFUNSTAT Return value for the procedure. Output.
MESSAGE-STRING Basic explanation for the error; up to 256 bytes in length. Output.
DETAIL-STRING Particulars of an error, such as filename; up to 256 bytes in length. Output.
Return Values
Error number of the most recent GeoStan error.
-1 |
No error. |
0 through 99 |
Indicates the actual DOS error values. |
100 |
Unclassified error. |
101 |
Unknown error. |
102 |
Invalid file signature. |
103 |
Table overflow. |
104 |
Insufficient memory. |
105 |
File not found. |
106 |
Invalid argument to a procedure. |
107 |
File is out of date. |
108 |
Invalid license filename, path, or incorrect password. |
109 |
Invalid GsFind call - cannot match an address and a geocode in the same GsFind call. |
110 |
Could not determine centerline. |
111 |
Invalid checksum on file contents. |
112 |
System exception (e.g. access violation). |
Alternates
GSERRGTX