GSINIT - 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. Initializes GeoStan.

Syntax

01 GSID            PIC S9(9) BINARY.
01 LSTATUS         PIC  9(9) BINARY.
01 GSOPTIONS       PIC  9(9) BINARY.
* PPATH AND Z4DIR: ONLY VALID VALUES ARE BLANK OR "HIPER". THEY ARE ONLY USED IN GSINIT
*
01 PPATH           PIC X(12).
01 Z4DIR           PIC X(12).
*
CALL "GSINIT" USING GSOPTIONS, PPATH, Z4DIR, LSTATUS, GSID.

Arguments

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

GSOPTIONS   Specifies which components of GeoStan to initialize.

GS-FILE-ADDR-CODE

Loads the files necessary for address geocoding.

GS-FILE-Z9-CODE

Loads the Z9 file for centroid geocoding.

GS-FILE-SPATIAL-QUERY

Loads spatial query files. If GeoStan cannot load the spatial query files, GSINIT fails. You can verify that GeoStan loads the files by checking the LStatus parameter in GSINIT.

Except for a few cases, you should always specify GS-FILE-ADDR-CODE and GS-FILE-Z9-CODE. Input.

PPATH   List of paths to search for necessary files. Set this argument to either " " or to "HIPER", which loads the GSD file into hyperspace (OS/390 extended memory). Other values are ignored. Input.

Z4DIR   Name of the ZIP + 4 directory file. Set this argument to either " " or to "HIPER", which loads the Z9 file into hyperspace (OS/390 extended memory). GeoStan ignores other values. Input.

LSTATUS   Pointer to a long integer that specifics which components GeoStan successfully initialized. Output.

GeoStan uses the following constants to test each significant bit:

GS-FILE-CBSA-DIR

Successfully loaded The CBSA lookup file (cbsac.dir).

GS-FILE-CITY-DIR

Successfully loaded the City lookup file (Ctyst.dir).

GS-FILE-EWS

Successfully loaded the EWS file (ews.txt).

GS-FILE-EXPIRED

All GSD files have expired (see Return Values section below).

GS-FILE-AUXILIARY

Successfully loaded the auxiliary file (.gax).

GS-FILE-GEO-DIR

Successfully loaded the GeoStan directory file (*.gsd).

GS-FILE-LICENSE

Successfully loaded the GeoStan license file.

GS-FILE-LOT

Successfully loaded the eLOT and Z4Change file (Us.gsl)

GS-FILE-PARSE-TABLES

Successfully loaded the parsing tables (Parse.dir).

GS-FILE-SPATIAL-QUERY

Successfully loaded the spatial query file (finmbr.dat).

GS-FILE-ZIP4-CENT-DIR

Successfully loaded the ZIP + 4 centroid file (Z4.dir).

GS-FILE-ZIPMOVE

Successfully loaded the ZIPMove file (Us.gsz).

GS-FILE-ZIP9-IDX

Successfully loaded the ZIP9 index file (Zip9.gsu).

Return Values

Returns a valid GSID if the system initializes correctly.

Returns 0 if GeoStan did not initialize.

GSINIT can fail for any of the following reasons:

  • GeoStan did not find the necessary files. Check LSTATUS for the files GeoStan successfully found (and by omission, the files not found).

  • Not enough memory for GeoStan to initialize.

  • All available GSD files have expired. In this situation, GSINIT returns GS-FILE-EXPIRED in the LSTATUS argument.

Prerequisites

GSSLIC

Notes

Must be called before GSSCACHE, GSSLIC, or GSSRELD.

If you are using the GSSCACHE and GSSRELD procedures, You must call these before GSINIT.

You must call GSINIT before any other GeoStan procedure that uses the handle that GSINIT returns.