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


IOCTL call

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

The IOCTL call is used to control certain operating characteristics for a socket.

Before you issue an IOCTL call, you must load a value representing the characteristic that you want to control into the COMMAND field.

The variable length parameters REQARG and RETARG are arguments that are passed to and returned from IOCTL. The length of REQARG and RETARG is determined by the value that you specify in COMMAND. See Table 1 for information about REQARG and RETARG.

The following requirements apply to this call:
Requirement Requirement
Authorization: Supervisor state or problem state, any PSW key
Dispatchable unit mode: Task
Cross memory mode: PASN = HASN
Amode: 31-bit or 24-bit
Note: See "Addressability mode (Amode) considerations" under Environmental restrictions and programming requirements for the Callable Socket API.
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 IOCTL call instructions.

Figure 1. IOCTL call instruction example
       WORKING-STORAGE SECTION.
       01  SOKET-FUNCTION         PIC X(16) VALUE 'IOCTL'.
       01  S                      PIC 9(4)  BINARY.
       01  COMMAND                PIC 9(4)  BINARY.
 
       01  IFREQ.
        05 NAME                   PIC X(16).
        05 FAMILY                 PIC 9(4)  BINARY.
        05 PORT                   PIC 9(4)  BINARY.
        05 ADDRESS                PIC 9(8)  BINARY.
        05 FILLER                 PIC X(8).
 
       01  IFREQOUT.
        05 NAME                   PIC X(16).
        05 FAMILY                 PIC 9(4)  BINARY.
        05 PORT                   PIC 9(4)  BINARY.
        05 ADDRESS                PIC 9(8)  BINARY.
        05 FILLER                 PIC X(8).
 
       01  GRP-IOCTL-TABLE.
        05 IOCTL-ENTRY OCCURS 1 TO max TIMES DEPENDING ON count.
         10 NAME                  PIC X(16).
         10 FAMILY                PIC 9(4)  BINARY.
         10 PORT                  PIC 9(4)  BINARY.
         10 ADDRESS               PIC 9(8)  BINARY.
         10 FILLER                PIC X(8).
 
        01 IOCTL-REQARG           USAGE IS POINTER.
        01 IOCTL-RETARG           USAGE IS POINTER.
        01 ERRNO                  PIC 9(8) BINARY.
        01 RETCODE                PIC 9(8) BINARY.
 
 
    PROCEDURE DIVISION.
         CALL 'EZASOKET' USING SOC-FUNCTION S COMMAND REQARG
               RETARG 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