GSLACINR - geostan_1 - 2024.01

GeoStan Geocoding Suite Reference for Windows, Linux, and z/OS

Product type
Software
Portfolio
Locate
Product family
GeoStan Geocoding Suite
Product
GeoStan Geocoding Suite > GeoStan
Version
2024.01
Language
English
Product name
GeoStan
Title
GeoStan Geocoding Suite Reference for Windows, Linux, and z/OS
Copyright
2024
First publish date
1994
Last updated
2024-07-29
Published on
2024-07-29T23:01:18.924000

Deprecated. Initialize GeoStan for LACSLink.

Syntax

01 GSID            PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT       PIC S9(9) BINARY.
01 STRUCT-SIZE     PIC S9(9) BINARY.
01 W-HAVE-MESSAGE  PIC S9(9) BINARY.
01 W-ERROR-MSG     PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL  PIC X(256) VALUE LOW-VALUES.
*
CALL 'GSLACINR' USING GSID, GS-LACSLINK-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.

Arguments

GSID   ID returned by GSINIT for the current instance of GeoStan. Input.

GS-LACSLINK-INIT-STRUCT    Also defined in GEOSTAN.H. This structure contains the following:

GS-LIS-STRUCT-VERSION    LACSLink version number. Set to GS-GEOSTAN-VERSION. Input.

GS-LIS-OPTIONS    Reserved for future implementation. Input.

GS-LIS-STATUS    Indicates the successful initialization of LACSLink. The following table contains the constants used to test each significant bit. Output.

GS-LACSLINK-FILE-LICENSE

LACSLink license loaded successfully.

GS-LACSLINK-FILE-ALL

LACSLink data loaded successfully.

GS-LIST-SECURITY-KEY    Security key to initialize LACSLink functionality. Input.

STRUCTSIZE   Size of the LACSINITSTRUCT data structure. Input.

Return Values

GS-SUCCESS   Initialized successfully.

GS-ERROR   Failed to initialize.

Prerequisites

GSINIT

Example

Initialize GeoStan for LACSLink.

***********  WORKING STORAGE VARIABLES ***********************
01 GSID            PIC S9(9) BINARY VALUE 0.
01 GSFUNSTAT       PIC S9(9) BINARY.
01 STRUCT-SIZE     PIC S9(9) BINARY.
01 W-HAVE-MESSAGE  PIC S9(9) BINARY.
01 W-ERROR-MSG     PIC X(256) VALUE LOW-VALUES.
01 W-ERROR-DETAIL  PIC X(256) VALUE LOW-VALUES.
             
COPY GSCONST.
             
*******  SAMPLE CODE TO INITIALIZE LACS/LINK *****************
**** PLACE AFTER CALL TO GSINIT    ***************************
MOVE GS-GEOSTAN-VERSION       TO GS-LIS-STRUCT-VERSION.
MOVE GS-LIS-COB-STRUCT-SIZE   TO STRUCT-SIZE.
             
CALL 'GSLACINR' USING GSID, GS-LACSLINK-INIT-STRUCT, STRUCT-SIZE, GSFUNSTAT.
             
IF GSFUNSTAT = GS-SUCCESS
DISPLAY 'LACS INITIALIZED SUCCESSFULLY'
ELSE
DISPLAY '********************************'
DISPLAY 'LACS FAILED TO INITIALIZE'
DISPLAY 'GSFUNSTAT IS:', GSFUNSTAT
DISPLAY 'GSID IS:', GSID
DISPLAY 'GS-LACSLINK-INIT-STRUCT:', GS-DPV-INIT-STRUCT
DISPLAY 'STRUCT-SIZE IS:', STRUCT-SIZE
DISPLAY '********************************'
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
PERFORM UNTIL W-HAVE-MESSAGE IS EQUAL TO ZERO
CALL 'GSERRGTX' USING GSID, W-ERROR-MSG, W-ERROR-DETAIL, GSFUNSTAT
DISPLAY 'W-ERROR-MSG:', W-ERROR-MSG
DISPLAY 'W-ERROR-DETAIL:', W-ERROR-DETAIL
CALL 'GSERRHAS' USING GSID, W-HAVE-MESSAGE
END-PERFORM

After you have initialized LACSLink and called GSSFIND for an address, you can then call GSDATGET and request any of the following output fields, which are included in the copy member GSCONST:

  • GS-LACS-FLAG

  • GS-LACSLINK-IND

  • GS-LACSLINK-RETCODE