z/OS Communications Server: IP CICS Sockets Guide
Previous topic | Next topic | Contents | Contact z/OS | Library | PDF


RECVMSG call

z/OS Communications Server: IP CICS Sockets Guide
SC27-3649-00

The RECVMSG call receives messages on a socket with descriptor S and stores them in an array of message headers. If a datagram packet is too long to fit in the supplied buffers, datagram sockets discard extra bytes.

For datagram protocols, the RECVMSG call returns the source address associated with each incoming datagram. For connection-oriented protocols like TCP, the GETPEERNAME call returns the address associated with the other end of the connection.

The following requirements apply to this call:
Requirement Description
Authorization: Supervisor state or problem state, any PSW key
Dispatchable unit mode: Task
Cross memory mode: PASN = HASN
Amode: 31-bit or 24-bit
ASC mode: Primary address space control (ASC) mode
Interrupt status: Enabled for interrupts
Locks: Unlocked
Control parameters: All parameters must be addressable by the caller and in the primary address space

Figure 1 shows an example of RECVMSG call instructions.

Figure 1. RECVMSG call instruction example (Part 1 of 2)
WORKING-STORAGE SECTION.
            01  SOC-FUNCTION    PIC X(16)  VALUE IS 'RECVMSG'.
            01  S               PIC 9(4)   BINARY.
            01  MSG.
                03  NAME            USAGE IS POINTER.
                03  NAME-LEN        USAGE IS POINTER.
                03  IOV             USAGE IS POINTER.
                03  IOVCNT          USAGE IS POINTER.
                03  ACCRIGHTS       USAGE IS POINTER.
                03  ACCRLEN         USAGE IS POINTER.
 
            01  FLAGS           PIC 9(8)   BINARY.
            01  NO-FLAG         PIC 9(8)   BINARY VALUE IS 0.
            01  OOB             PIC 9(8)   BINARY VALUE IS 1.
            01  PEEK            PIC 9(8)   BINARY VALUE IS 2.
            01  ERRNO           PIC 9(8)   BINARY.
            01  RETCODE         PIC S9(8)  BINARY.
 
       LINKAGE SECTION.
 
            01 L1.
               03 RECVMSG-IOVECTOR.
                  05 IOV1A               USAGE IS POINTER.
                  05 IOV1AL              PIC 9(8) COMP.
                  05 IOV1L               PIC 9(8) COMP.
                  05 IOV2A               USAGE IS POINTER.
                  05 IOV2AL              PIC 9(8) COMP.
                  05 IOV2L               PIC 9(8) COMP.
                  05 IOV3A               USAGE IS POINTER.
                  05 IOV3AL              PIC 9(8) COMP.
                  05 IOV3L               PIC 9(8) COMP.
 
               03 RECVMSG-BUFFER1     PIC X(16).
               03 RECVMSG-BUFFER2     PIC X(16).
               03 RECVMSG-BUFFER3     PIC X(16).
               03 RECVMSG-BUFNO       PIC 9(8) COMP.

        * 
        * IPv4 Socket Address Structure. 
        * 
               03 RECVMSG-NAME. 
                  05 FAMILY           PIC 9(4) BINARY. 
                  05 PORT             PIC 9(4) BINARY. 
                  05 IP-ADDRESS       PIC 9(8) BINARY. 
                  05 RESERVED         PIC X(8). 
        * 
        * IPv6 Socket Address Structure. 
        * 
              03 RECVMSG-NAME. 
                 05 FAMILY            PIC 9(4) BINARY. 
                 05 PORT              PIC 9(4) BINARY. 
                 05 FLOW-INFO         PIC 9(8) BINARY. 
                 05 IP-ADDRESS. 
                    10 FILLER         PIC 9(16) BINARY. 
                    10 FILLER         PIC 9(16) BINARY. 
                 05 SCOPE-ID          PIC 9(8) BINARY. 
Figure 2. RECVMSG call instruction example (Part 2 of 2)
PROCEDURE DIVISION USING L1.
 
                  SET NAME TO ADDRESS OF RECVMSG-NAME.
                  MOVE LENGTH OF RECVMSG-NAME TO NAME-LEN.
                  SET IOV TO ADDRESS OF RECVMSG-IOVECTOR.
                  MOVE 3 TO RECVMSG-BUFNO.
                  SET IOVCNT TO ADDRESS OF RECVMSG-BUFNO.
                  SET IOV1A TO ADDRESS OF RECVMSG-BUFFER1.
                  MOVE 0 TO MSG-IOV1AL.
                  MOVE LENGTH OF RECVMSG-BUFFER1 TO IOV1L.
                  SET IOV2A TO ADDRESS OF RECVMSG-BUFFER2.
                  MOVE 0 TO IOV2AL.
                  MOVE LENGTH OF RECVMSG-BUFFER2 TO IOV2L.
                  SET IOV3A TO ADDRESS OF RECVMSG-BUFFER3.
                  MOVE 0 TO IOV3AL.
                  MOVE LENGTH OF RECVMSG-BUFFER3 TO IOV3L.
                  SET ACCRIGHTS TO NULLS.
                  SET ACCRLEN TO NULLS.
                  MOVE 0 TO FLAGS.
                  MOVE SPACES TO RECVMSG-BUFFER1.
                  MOVE SPACES TO RECVMSG-BUFFER2.
                  MOVE SPACES TO RECVMSG-BUFFER3.
 
           CALL 'EZASOKET' USING SOC-FUNCTION S MSG FLAGS ERRNO RETCODE.

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

Go to the previous page Go to the next page




Copyright IBM Corporation 1990, 2014