SPOFFPG - spatial_geostan - 2024.00

Spatial+ Reference for Windows, UNIX/Linux, z/OS

Product type
Software
Portfolio
Locate
Product family
GeoStan Geocoding Suite
Product
GeoStan Geocoding Suite > Spatial+
Version
2024.00
Language
English
Product name
Spatial+
Title
Spatial+ Reference for Windows, UNIX/Linux, z/OS
Copyright
2024
First publish date
1994
Last updated
2024-05-07
Published on
2024-05-07T22:16:04.316305

Finds first polygon in the object file overlapping the input polygon.

Syntax

01 SPHANDLE PIC 9(9) BINARY.

01 POINTS OCCURS 8 TIMES.

05 PNTS PIC S9(9) BINARY.

01 NUMPTSPERPOLY OCCURS 2 TIMES.

05 NUMPOINTS PIC S9(9) BINARY.

01 NUMPOLYGONS PIC 9(9) BINARY.

01 NAMEBUFFER X(80).

01 BUFSIZE PIC 9(9) BINARY VALUE 80.

*

CALL ‘SPOFFPG'

USING SPHANDLE, POINTS, NUMPTSPERPOLY, NUMPOLYGONS, NAMEBUFFER, BUFSIZE, SPRETCODE.

Arguments

SPHANDLE File handle from SPOFOP. Input.

PNTS Input region; an array of x,y point values. Input. NUMPOINTS Array of point counts for each polygon in the region. Input. NUMPOLYGONS Number of polygons in input region. Input.

NAMEBUFFER A buffer to be filled with the identifier of the object from the object file which the input polygon overlaps. Output.

BUFSIZE The size of the buffer that contains the identifier of the object which the input polygon overlaps. If the buffer size is smaller than the identifier, the identifier is truncated. Input.

Return Values

PIP-ERROR

PIP-NOT-FOUND

PIP-REGION-OVERLAP PIP-INPUT-IN-OBJECT PIP-OBJECT-IN-INPUT

PIP-OBJECT-EQUALS-INPUT

SPOFOP.

Prerequisites

Alternates

SPOFFPG, SPCKROX.

Notes

This procedure compares an input polygon with polygons in an existing object file. If any region in the object file intersects with the input region, the intersection type is returned. If no overlapping region is found, the procedure returns PIP-NOT-FOUND.