z/OS Communications Server: IP Sockets Application Programming Interface Guide and Reference
Previous topic | Next topic | Contents | Contact z/OS | Library | PDF


EZACIC09

z/OS Communications Server: IP Sockets Application Programming Interface Guide and Reference
SC27-3660-00

The GETADDRINFO call was derived from the C socket call that return a structure known as RES. A given TCP/IP host can have multiple sets of NAMES. TCP/IP uses indirect addressing to connect the variable number of NAMES in the RES structure that is returned by the GETADDRINFO call. If you are coding in PL/I or assembler language, the RES structure can be processed in a relatively straight-forward manner. However, if you are coding in COBOL, RES can be more difficult to process and you should use the EZACIC09 subroutine to process it for you. It works as follows:

  1. GETADDRINFO returns a RES structure that indirectly addresses the lists of socket address structures.
  2. Upon return from GETADDRINFO, your program calls EZACIC09 and passes it the address of the next address information structure as referenced by the NEXT argument. EZACIC09 processes the structure and returns the following information:
    1. The socket address structure
    2. The next address information structure
  3. If the GETADDRINFO call returns more than one socket address structure the application program should repeat the call to EZACIC09 until all socket address structures have been retrieved.

Figure 1 shows an example of EZACIC09 call instructions.

WORKING-STORAGE SECTION.
      *
      * Variables used for the GETADDRINFO call
      *
       01 getaddrinfo-parms.
          02 node-name pic x(255).
          02 node-name-len pic 9(8) binary.
          02 service-name pic x(32).
          02 service-name-len pic 9(8) binary.
          02 canonical-name-len pic 9(8) binary.
          02 ai-passive pic 9(8) binary value 1.
          02 ai-canonnameok pic 9(8) binary value 2.
          02 ai-numerichost pic 9(8) binary value 4.
          02 ai-numericserv pic 9(8) binary value 8.
          02 ai-v4mapped pic 9(8) binary value 16.
          02 ai-all pic 9(8) binary value 32.
          02 ai-addrconfig pic 9(8) binary value 64.
      *
      * Variables used for the EZACIC09 call
      *
       01 ezacic09-parms.
          02 res usage is pointer.
          02 res-name-len pic 9(8) binary.
          02 res-canonical-name pic x(256).
          02 res-name usage is pointer.
          02 res-next-addrinfo usage is pointer.
      *
      * Socket address structure
      *
       01 server-socket-address.
          05 server-family pic 9(4) Binary Value 19.
          05 server-port pic 9(4) Binary Value 9997.
          05 server-flowinfo pic 9(8) Binary Value 0.
          05 server-ipaddr.
             10 filler pic 9(16) binary value 0.
             10 filler pic 9(16) binary value 0.
          05 server-scopeid pic 9(8) Binary Value 0.

       LINKAGE SECTION.
       01 L1.
          03 HINTS-ADDRINFO.
             05 HINTS-AI-FLAGS PIC 9(8) BINARY.
             05 HINTS-AI-FAMILY PIC 9(8) BINARY.
             05 HINTS-AI-SOCKTYPE PIC 9(8) BINARY.
             05 HINTS-AI-PROTOCOL PIC 9(8) BINARY.
             05 FILLER PIC 9(8) BINARY.
             05 FILLER PIC 9(8) BINARY.
             05 FILLER PIC 9(8) BINARY.
             05 FILLER PIC 9(8) BINARY.
          03 HINTS-ADDRINFO-PTR USAGE IS POINTER.
          03 RES-ADDRINFO-PTR USAGE IS POINTER.
      *
      * RESULTS ADDRESS INFO
      *
       01 RESULTS-ADDRINFO.
          05 RESULTS-AI-FLAGS PIC 9(8) BINARY.
          05 RESULTS-AI-FAMILY PIC 9(8) BINARY.
          05 RESULTS-AI-SOCKTYPE PIC 9(8) BINARY.
          05 RESULTS-AI-PROTOCOL PIC 9(8) BINARY.
          05 RESULTS-AI-ADDR-LEN PIC 9(8) BINARY.
          05 RESULTS-AI-CANONICAL-NAME USAGE IS POINTER.
          05 RESULTS-AI-ADDR-PTR USAGE IS POINTER.
          05 RESULTS-AI-NEXT-PTR USAGE IS POINTER.
      *
      * SOCKET ADDRESS STRUCTURE FROM EZACIC09.
      *
       01 OUTPUT-NAME-PTR USAGE IS POINTER.
       01 OUTPUT-IP-NAME.
          03 OUTPUT-IP-FAMILY PIC 9(4) BINARY.
          03 OUTPUT-IP-PORT PIC 9(4) BINARY.
          03 OUTPUT-IP-SOCK-DATA PIC X(24).
          03 OUTPUT-IPV4-SOCK-DATA REDEFINES OUTPUT-IP-SOCK-DATA.
             05 OUTPUT-IPV4-IPADDR PIC 9(8) BINARY.
             05 FILLER PIC X(20).
          03 OUTPUT-IPV6-SOCK-DATA REDEFINES OUTPUT-IP-SOCK-DATA.
             05 OUTPUT-IPV6-FLOWINFO PIC 9(8) BINARY.
             05 OUTPUT-IPV6-IPADDR.
                10 FILLER PIC 9(16) BINARY.
                10 FILLER PIC 9(16) BINARY.
             05 OUTPUT-IPV6-SCOPEID PIC 9(8) BINARY.
       PROCEDURE DIVISION USING L1.
      *
      * Get and address from the resolver.
      *
           move 'yournodename' to node-name.
           move 12 to node-name-len.
           move spaces to service-name.
           move 0 to service-name-len.
           move af-inet6 to hints-ai-family.
           move 49 to hints-ai-flags
           move 0 to hints-ai-socktype.
           move 0 to hints-ai-protocol.
           set address of results-addrinfo to res-addrinfo-ptr.
           set hints-addrinfo-ptr to address of hints-addrinfo.
           call 'EZASOKET' using soket-getaddrinfo
                                 node-name node-name-len
                                 service-name service-name-len
                                 hints-addrinfo-ptr
                                 res-addrinfo-ptr
                                 canonical-name-len
                                 errno retcode.
      *
      * Use EZACIC09 to extract the IP address
      *
           set address of results-addrinfo to res-addrinfo-ptr.
           set res to address of results-addrinfo.
           move zeros to res-name-len.
           move spaces to res-canonical-name.
           set res-name to nulls.
           set res-next-addrinfo to nulls.
           call 'EZACIC09' using res
                                 res-name-len
                                 res-canonical-name
                                 res-name
                                 res-next-addrinfo
                                 retcode.
           set address of output-ip-name to res-name.
           move output-ipv6-ipaddr to server-ipaddr.
Figure 1. EZACIC09 call instruction example

For equivalent PL/I and assembler language declarations, see Converting parameter descriptions.

Parameter values set by the application:
RES
This fullword binary field must contain the address of the ADDRINFO structure (as returned by the GETADDRINFO call). This variable is the same as the RES variable in the GETADDRINFO socket call.
RES-NAME-LEN
A fullword binary field that will contain the length of the socket address structure as returned by the GETADDRINFO call.
Parameter values returned to the application:
Description
RES-CANONICAL-NAME
A field large enough to hold the canonical name. The maximum field size is 256 bytes. The canonical name length field will indicate the length of the canonical name as returned by the GETADDRINFO call.
RES-NAME
The address of the subsequent socket address structure.
RES-NEXT
The address of the next address information structure.
RETURN-CODE
CODE This fullword binary field contains the EZACIC09 return code:
Value
Description
0
Successful call.
-1
Invalid RES address.

Go to the previous page Go to the next page




Copyright IBM Corporation 1990, 2014