EXEC interface block fields

An application program can read all the fields in the EXEC interface block (EIB) of the associated task by name. An application must not change the contents of any of the fields, other than through an EXEC CICS command.

For each EIB field, the contents and format (for each of the application programming languages COBOL, C, PL/I, and Assembler) are given. Fields explained are EIBAID, EIBATT, EIBCALEN, EIBCOMPL, EIBCONF, EIBCPOSN, EIBDATE, EIBDS, EIBEOC, EIBERR, EIBERRCD, EIBFMH, EIBFN, EIBFREE, EIBNODAT, EIBRCODE, EIBRECV, EIBREQID, EIBRESP, EIBRESP2, EIBRLDBK, EIBRSRCE, EIBSIG, EIBSYNC, EIBSYNRB, EIBTASKN, EIBTIME, EIBTRMID, and EIBTRNID.

All fields contain binary zeros in the absence of meaningful information. Fields are listed in alphabetic order.

EIBAID
Contains the attention identifier (AID) associated with the last terminal control or basic mapping support (BMS) input operation from a display device such as the 3270.
COBOL:     PIC X(1).
C:         unsigned char eibaid;
PL/I:      CHAR(1)
Assembler: CL1
EIBATT
Indicates that the RU contains attach header data (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibatt;
PL/I:      CHAR(1)
Assembler: CL1
EIBCALEN
Contains the length of the communication area that has been passed to the application program from the last program, using the COMMAREA and LENGTH options. If no communication area is passed, this field contains binary zeros.
COBOL:     PIC S9(4) COMP.
C:         short int eibcalen;
PL/I:      FIXED BIN(15)
Assembler: H
EIBCOMPL
Indicates, on a terminal control RECEIVE command, whether the data is complete (X'FF'). If the NOTRUNCATE option has been used on the RECEIVE command, CICS® retains data in excess of the amount requested via the LENGTH or MAXLENGTH option. EIBRECV is set indicating that further RECEIVE commands are required. EIBCOMPL is not set until the last of the data has been retrieved.
EIBCOMPL is always set when a RECEIVE command without the NOTRUNCATE option is executed.
COBOL:     PIC X(1).
C:         unsigned char eibcompl;
PL/I:      CHAR(1)
Assembler: CL1
EIBCONF
Indicates that a CONFIRM request has been received (X'FF') for an APPC conversation.
COBOL:     PIC X(1).
C:         unsigned char eibconf;
PL/I:      CHAR(1)
Assembler: CL1
EIBCPOSN
Contains the cursor address (position) associated with the last terminal control or basic mapping support (BMS) input operation from a display device such as the 3270.
COBOL:     PIC S9(4) COMP.
C:         short int eibcposn;
PL/I:      FIXED BIN(15)
Assembler: H
EIBDATE
Contains the date the task is started; this field is updated by the ASKTIME command. The date is in packed decimal form (0CYYDDD+) where C shows the century with values 0 for the 1900s and 1 for the 2000s. For example, the date 31 December 1999 has the EIBDATE value of 0099365 and the date 1 January 2000 has an EIBDATE value of 0100001.

At midnight, if EIBTIME has the value of 0240000+, the value of EIBDATE is the day that has ended. If EIBTIME has the value of 0000000+, the value of EIBDATE is the day that is just beginning.

COBOL:     PIC S9(7) COMP-3.
C:         char eibdate [4];
PL/I:      FIXED DEC(7,0)
Assembler: PL4
EIBDS
Contains the symbolic identifier of the last data set referred to in a file control request.
COBOL:     PIC X(8).
C:         char eibds [8];
PL/I:      CHAR(8)
Assembler: CL8
EIBEOC
Indicates that an end-of-chain indicator appears in the RU just received (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibeoc;
PL/I:      CHAR(1)
Assembler: CL1
EIBERR
Indicates that an error has been received (X'FF') on an APPC conversation.
COBOL:     PIC X(1).
C:         unsigned char eiberr;
PL/I:      CHAR(1)
Assembler: CL1
EIBERRCD
When EIBERR is set, contains the error code that has been received. The following values can be returned in the first two bytes of EIBERRCD:
X'0889'
Conversation error detected.
X'0824'
SYNCPOINT ROLLBACK requested.
COBOL:     PIC X(4).
C:         char eiberrcd [4];
PL/I:      CHAR(4)
Assembler: CL4

See CICS mapping to the APPC architecture for information about other EIBERRCD values that can occur.

EIBFMH
Indicates that the user data received or retrieved contains an FMH (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibfmh;
PL/I:      CHAR(1)
Assembler: CL1
EIBFN
Contains a code that identifies the last CICS command issued by the task.
COBOL:     PIC X(2).
C:         char eibfn [2];
PL/I:      CHAR(2)
Assembler: CL2

See Function codes of EXEC CICS commands.

EIBFREE
Indicates that the application program cannot continue using the facility. The application program should either free the facility or should terminate so that the facility is freed by CICS (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibfree;
PL/I:      CHAR(1)
Assembler: CL1
EIBNODAT
Indicates that no data has been sent by the remote application (X'FF'). A message has been received from the remote system that conveyed only control information. For example, if the remote application executed a SEND command with the WAIT option, any data would be sent across the link. If the remote application then executed a SEND INVITE command without using the FROM option to transmit data at the same time, it would be necessary to send the INVITE instruction across the link by itself. In this case, the receiving application finds EIBNODAT set. The use of this field is restricted to application programs holding conversations across APPC links only.
COBOL:     PIC X(1).
C:         unsigned char eibnodat;
PL/I:      CHAR(1)
Assembler: CL1
EIBRCODE
Contains the CICS response code returned after the function requested by the last CICS command to be issued by the task has been completed.
Note: For commands where EIBRESP and EIBRESP2 are used for interrogating the resulting condition of an executed command, byte 3 of EIBRCODE has the same value as EIBRESP. Any further information is in EIBRESP2 rather than EIBRCODE. For a normal response, this field contains hexadecimal zeros (6 X'00').
Almost all of the information in this field can be used within application programs by the HANDLE CONDITION command.
COBOL:     PIC X(6).
C:         char eibrcode [6];
PL/I:      CHAR(6)
Assembler: CL6

The following list contains the values of the bytes together with the names of the conditions associated with the return codes.

See the notes at the end of the list of values for explanations of the numbers following some of the conditions.
EIBFN EIBRCODE Condition
02 .. E0 .. .. .. .. .. INVREQ
     
04 .. 04 .. .. .. .. .. EOF
04 .. 10 .. .. .. .. .. EODS
04 .. C1 .. .. .. .. .. EOF
04 .. C2 .. .. .. .. .. ENDINPT
04 .. D0 .. .. .. .. .. SYSIDERR (see note 1)
04 .. D2 .. .. .. .. .. SESSIONERR (see note 2)
04 .. D3 .. .. .. .. .. SYSBUSY (see note 3)
04 .. D4 .. .. .. .. .. SESSBUSY
04 .. D5 .. .. .. .. .. NOTALLOC
04 .. E0 .. .. .. .. .. INVREQ (see note 4)
04 .. E1 .. .. .. .. .. LENGERR (see note 5)
04 .. E3 .. .. .. .. .. WRBRK
04 .. E4 .. .. .. .. .. RDATT
04 .. E5 .. .. .. .. .. SIGNAL
04 .. E6 .. .. .. .. .. TERMIDERR
04 .. E7 .. .. .. .. .. NOPASSBKRD
04 .. E8 .. .. .. .. .. NOPASSBKWR
04 .. EA .. .. .. .. .. IGREQCD
04 .. EB .. .. .. .. .. CBIDERR
04 .. EC .. .. .. .. .. PARTNERIDERR
04 .. ED .. .. .. .. .. NETNAMEIDERR
04 .. F1 .. .. .. .. .. TERMERR
04 .. .. 20 .. .. .. .. EOC
04 .. .. 40 .. .. .. .. INBFMH
04 .. .. .. .. F6 .. .. NOSTART
04 .. .. .. .. F7 .. .. NONVAL
     
06 .. 01 .. .. .. .. .. FILENOTFOUND
06 .. 02 .. .. .. .. .. ILLOGIC (see note 6)
06 .. 03 .. .. .. .. .. LOCKED
06 .. 05 .. .. .. .. .. RECORDBUSY
06 .. 08 .. .. .. .. .. INVREQ
06 .. 0C .. .. .. .. .. NOTOPEN
06 .. 0D .. .. .. .. .. DISABLED
06 .. 0F .. .. .. .. .. ENDFILE
06 .. 80 .. .. .. .. .. IOERR (see note 6)
06 .. 81 .. .. .. .. .. NOTFND
06 .. 82 .. .. .. .. .. DUPREC
06 .. 83 .. .. .. .. .. NOSPACE
06 .. 84 .. .. .. .. .. DUPKEY
06 .. 85 .. .. .. .. .. SUPPRESSED
06 .. 86 .. .. .. .. .. LOADING
06 .. D0 .. .. .. .. .. SYSIDERR (see note 1)
06 .. D1 .. .. .. .. .. ISCINVREQ
06 .. D6 .. .. .. .. .. NOTAUTH
06 .. E1 .. .. .. .. .. LENGERR
     
08 .. 01 .. .. .. .. .. QZERO
08 .. 02 .. .. .. .. .. QIDERR
08 .. 04 .. .. .. .. .. IOERR
08 .. 08 .. .. .. .. .. NOTOPEN
08 .. 10 .. .. .. .. .. NOSPACE
08 .. C0 .. .. .. .. .. QBUSY
08 .. D0 .. .. .. .. .. SYSIDERR (see note 1)
08 .. D1 .. .. .. .. .. ISCINVREQ
08 .. D6 .. .. .. .. .. NOTAUTH
08 .. D7 .. .. .. .. .. DISABLED
08 .. E0 .. .. .. .. .. INVREQ
08 .. E1 .. .. .. .. .. LENGERR
     
0A .. 01 .. .. .. .. .. ITEMERR
0A .. 02 .. .. .. .. .. QIDERR
0A .. 04 .. .. .. .. .. IOERR
0A .. 08 .. .. .. .. .. NOSPACE
0A .. 20 .. .. .. .. .. INVREQ
0A .. D0 .. .. .. .. .. SYSIDERR (see note 1)
0A .. D1 .. .. .. .. .. ISCINVREQ
0A .. D6 .. .. .. .. .. NOTAUTH
0A .. E1 .. .. .. .. .. LENGERR
     
0C .. E0 .. .. .. .. .. INVREQ
0C .. E1 .. .. .. .. .. LENGERR
0C .. E2 .. .. .. .. .. NOSTG
     
0E .. 01 .. .. .. .. .. PGMIDERR
0E .. D6 .. .. .. .. .. NOTAUTH
0E .. D9 .. .. .. .. .. RESUNAVAIL
0E .. DA .. .. .. .. .. CHANNELERR
0E .. E0 .. .. .. .. .. INVREQ
0E .. E1 .. .. .. .. .. LENGERR
0E .. F1 .. .. .. .. .. TERMERR
     
10 .. 01 .. .. .. .. .. ENDDATA
10 .. 04 .. .. .. .. .. IOERR
10 .. 11 .. .. .. .. .. TRANSIDERR
10 .. 12 .. .. .. .. .. TERMIDERR
10 .. 20 .. .. .. .. .. EXPIRED
10 .. 81 .. .. .. .. .. NOTFND
10 .. D0 .. .. .. .. .. SYSIDERR (see note 1)
10 .. D1 .. .. .. .. .. ISCINVREQ
10 .. D6 .. .. .. .. .. NOTAUTH
10 .. D8 .. .. .. .. .. USERIDERR
10 .. D9 .. .. .. .. .. RESUNAVAIL
10 .. DA .. .. .. .. .. CHANNELERR
10 .. E1 .. .. .. .. .. LENGERR
10 .. E9 .. .. .. .. .. ENVDEFERR
10 .. FF .. .. .. .. .. INVREQ
     
12 .. 32 .. .. .. .. .. ENQBUSY
12 .. E0 .. .. .. .. .. INVREQ
12 .. E1 .. .. .. .. .. LENGERR
     
14 .. 01 .. .. .. .. .. JIDERR
14 .. 02 .. .. .. .. .. INVREQ
14 .. 05 .. .. .. .. .. NOTOPEN
14 .. 06 .. .. .. .. .. LENGERR
14 .. 07 .. .. .. .. .. IOERR
14 .. 09 .. .. .. .. .. NOJBUFSP
14 .. D6 .. .. .. .. .. NOTAUTH
     
16 .. 01 .. .. .. .. .. ROLLEDBACK
     
18 .. 01 .. .. .. .. .. INVREQ
18 .. 02 .. .. .. .. .. RETPAGE
18 .. 04 .. .. .. .. .. MAPFAIL
18 .. 08 .. .. .. .. .. INVMPSZ (see note 7)
18 .. 20 .. .. .. .. .. INVERRTERM
18 .. 40 .. .. .. .. .. RTESOME
18 .. 80 .. .. .. .. .. RTEFAIL
18 .. E1 .. .. .. .. .. LENGERR
18 .. E3 .. .. .. .. .. WRBRK
18 .. E4 .. .. .. .. .. RDATT
18 .. .. 02 .. .. .. .. PARTNFAIL
18 .. .. 04 .. .. .. .. INVPARTN
18 .. .. 08 .. .. .. .. INVPARTNSET
18 .. .. 10 .. .. .. .. INVLDC
18 .. .. 20 .. .. .. .. UNEXPIN
18 .. .. 40 .. .. .. .. IGREQCD
18 .. .. 80 .. .. .. .. TSIOERR
18 .. .. .. 01 .. .. .. OVERFLOW
18 .. .. .. 04 .. .. .. EODS
18 .. .. .. 08 .. .. .. EOC
18 .. .. .. 10 .. .. .. IGREQID
     
1A .. E0 .. .. .. .. .. INVREQ
1A .. 04 .. .. .. .. .. DSSTAT
1A .. 08 .. .. .. .. .. FUNCERR
1A .. 0C .. .. .. .. .. SELNERR
1A .. 10 .. .. .. .. .. UNEXPIN
1A .. E1 .. .. .. .. .. LENGERR
1A .. .. 11 .. .. .. .. EODS
1A .. .. 2B .. .. .. .. IGREQCD
1A .. .. .. 20 .. .. .. EOC
     
22 .. 80 .. .. .. .. .. INVEXITREQ
4A .. .. .. .. 01 .. .. INVREQ
     
56 .. .. .. .. 0D .. .. NOTFND
56 .. .. .. .. 10 .. .. INVREQ
56 .. .. .. .. 13 .. .. NOTOPEN
56 .. .. .. .. 14 .. .. ENDFILE
56 .. .. .. .. 15 .. .. ILLOGIC
56 .. .. .. .. 16 .. .. LENGERR
56 .. .. .. .. 2A .. .. NOSTG
56 .. .. .. .. 46 .. .. NOTAUTH
56 .. .. .. .. 50 .. .. NOSPOOL
56 .. .. .. .. 55 .. .. ALLOCERR
56 .. .. .. .. 56 .. .. STRELERR
56 .. .. .. .. 57 .. .. OPENERR
56 .. .. .. .. 58 .. .. SPOLBUSY
56 .. .. .. .. 59 .. .. SPOLERR
56 .. .. .. .. 5A .. .. NODEIDERR
Note:
  1. When SYSIDERR occurs, further information is provided in bytes 1 and 2 of EIBRCODE, as shown in Figure 1.
    Figure 1. Bytes 1 and 2 of EIBRCODE for SYSIDERR
     .. 04 00 .. .. ..   request was for a function
                         that is not valid.
     .. 04 04 .. .. ..   no session available and
                         NOQUEUE.
     .. 04 08 .. .. ..   modename not found (for APPC only).
     .. 04 0C .. .. ..   modename not valid (for APPC only).
     .. 04 10 .. .. ..   task canceled or timed
                         out during allocation (for APPC only).
     .. 04 14 .. .. ..   mode group is out of
                         service (for APPC only).
     .. 04 18 .. .. ..   close - DRAIN=ALL (for APPC only).
     .. 08 .. .. .. ..   sysid is not available.
     .. 08 00 .. .. ..   no session available,
                         all sessions are out
                         of service, or released,
                         or being quiesced.
     .. 08 04 .. .. ..   no session available,
                         request to queue rejected
                         by XZIQUE global user
                         exit program.
     .. 08 08 .. .. ..   no session available;
                         request rejected by XZIQUE
                         global user exit program.
     .. 0C xx .. .. ..   sysid definition error.
     .. 0C 00 .. .. ..   name not that of TCTSE.
     .. 0C 04 .. .. ..   name not that of remote
                         TCTSE.
     .. 0C 08 .. .. ..   mode name not found.
    
     .. 0C 0C .. .. ..   profile not found.
    

    Further information about SYSIDERR can be found in Syncpoint exchanges.

  2. When SESSIONERR occurs, further information is provided in bytes 1 and 2 of EIBRCODE, as shown in Figure 2.
    Figure 2. Bytes 1 and 2 of EIBRCODE for SESSIONERR
     .. 08 .. .. .. ..   session out of service
     .. 0C xx .. .. ..   session definition error
     .. 0C 00 .. .. ..   name not found
     .. 0C 0C .. .. ..   profile not found.

    Further information about SESSIONERR can be found in CICS-to-IMS applications: DTP.

  3. If SYSBUSY occurs on an ALLOCATE command that attempts to acquire a session to an APPC terminal or system, byte 3 of the EIBRCODE indicates where the error condition was detected as shown in Figure 3.
    Figure 3. Byte 3 of EIBRCODE for SYSBUSY
     .. .. .. 00 .. ..   the request was for a
                         session to a connected
                         terminal or system.
     .. .. .. 01 .. ..   the request was for a
                         session to a remotely
                         connected terminal or
                         system, and the error
                         occurred in the terminal-
                         owning region (TOR) or
                         an intermediate system.
     .. .. .. 02 .. ..   the request was for a
                         session to a remotely
                         connected terminal or
                         system, and the error
                         occurred in the
                         application-owning
                         region (AOR).

    Further information about SYSBUSY can be found in CICS-to-IMS applications: DTP.

  4. When INVREQ occurs during terminal control operations, further information is provided in bytes 1 or 3 of EIBRCODE as shown in Figure 4.
    Figure 4. Bytes 1 or 3 of EIBRCODE for INVREQ
     .. 24 .. .. .. ..   ISSUE PREPARE command -
                         STATE error.
     .. .. .. 04 .. ..   ALLOCATE command - TCTTE
                         already allocated.
     .. .. .. 08 .. ..   FREE command - TCTTE in
                         wrong state.
     .. .. .. 0C .. ..   CONNECT PROCESS command -
                         SYNCLVL 2 requested, but
                         cannot be supported on
                         the session in use.
     .. .. .. 10 .. ..   EXTRACT ATTACH command -
                         incorrect data.
     .. .. .. 14 .. ..   SEND command - CONFIRM
                         option specified, but
                         conversation not SYNCLVL 1.
     .. .. .. 18 .. ..   EXTRACT TCT command -
                         incorrect netname.
     .. .. .. 1C .. ..   an incorrect command has
                         been issued for the terminal
                         or logical unit in use.
     .. .. .. 20 .. ..   an incorrect command has
                         been issued for the LUTYPE6.2
                         conversation type in use.
     .. .. .. 28 .. ..   GETMAIN failure on ISSUE
                         PASS command.
     .. .. .. 2C .. ..   Command invalid in DPL
                         environment.
  5. When LENGERR occurs during terminal control operations, further information is provided in byte 1 of EIBRCODE, as shown in Figure 5.
    Figure 5. Byte 1 of EIBRCODE for LENGERR
     .. 00 .. .. .. ..   input data is overlong and
                         has been truncated.
     .. 04 .. .. .. ..   on output commands, an
                         incorrect (FROM)LENGTH has
                         been specified, either less
                         than zero or greater than
                         32 767.
     .. 08 .. .. .. ..   on input commands, an
                         incorrect (TO)LENGTH has
                         been specified, greater than
                         32 767.
     .. 0C .. .. .. ..   length error has occurred on
                         ISSUE PASS command.
    Note: This field is not used exclusively, and can take other values.
  6. When ILLOGIC or IOERR occurs during file control operations, further information is provided in field EIBRCODE, as shown in Figure 6.
    Figure 6. EIBRCODE for ILLOGIC or IOERR
     .. xx xx xx xx ..   BDAM response.
     .. xx .. .. .. ..   VSAM return code.
     .. .. xx .. .. ..   VSAM error code.
    where:
    byte 3 =
    VSAM problem determination code (ILLOGIC only)
    byte 4 =
    VSAM component code (ILLOGIC only)

    Details of these response codes are described in z/OS DFSMS Macro Instructions for Data Sets for VSAM, and z/OS DFSMS Using Data Sets for BDAM.

  7. When INVMPSZ occurs during BMS operations, byte 3 of field EIBRCODE contains the terminal code as shown in Figure 7.
    Figure 7. Byte 3 of EIBRCODE for INVMPSZ
     .. .. .. xx .. ..   terminal code.

    These are the same as the mapset suffixes shown in DFHMSD.

EIBRECV
Indicates that the application program is to continue receiving data from the facility by executing RECEIVE commands (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibrecv;
PL/I:      CHAR(1)
Assembler: CL1
EIBREQID
Contains the request identifier assigned to an interval control command by CICS; this field is not used when a request identifier is specified in the application program.
COBOL:     PIC X(8).
C:         char eibreqid [8];
PL/I:      CHAR(8)
Assembler: CL8
EIBRESP
Contains a number corresponding to the RESP condition that occurred. These numbers are listed (in decimal) for the conditions that can occur during execution of the commands described in this manual.
COBOL:     PIC S9(8) COMP
C:         long int eibresp;
PL/I:      FIXED BIN(31)
Assembler: F
No. Condition No. Condition
00 NORMAL 60 SESSBUSY
01 ERROR 61 NOTALLOC
02 RDATT 62 CBIDERR
03 WRBRK 63 INVEXITREQ
04 EOF 64 INVPARTNSET
05 EODS 65 INVPARTN
06 EOC 66 PARTNFAIL
07 INBFMH 69 USERIDERR
08 ENDINPT 70 NOTAUTH
09 NONVAL 71 VOLIDERR
10 NOSTART 72 SUPPRESSED
11 TERMIDERR 75 RESIDERR
12 FILENOTFOUND 80 NOSPOOL
13 NOTFND 81 TERMERR
14 DUPREC 82 ROLLEDBACK
15 DUPKEY 83 END
16 INVREQ 84 DISABLED
17 IOERR 85 ALLOCERR
18 NOSPACE 86 STRELERR
19 NOTOPEN 87 OPENERR
20 ENDFILE 88 SPOLBUSY
21 ILLOGIC 89 SPOLERR
22 LENGERR 90 NODEIDERR
23 QZERO 91 TASKIDERR
24 SIGNAL 92 TCIDERR
25 QBUSY 93 DSNNOTFOUND
26 ITEMERR 94 LOADING
27 PGMIDERR 95 MODELIDERR
28 TRANSIDERR 96 OUTDESCRERR
29 ENDDATA 97 PARTNERIDERR
30 INVTSREQ 98 PROFILEIDERR
31 EXPIRED 99 NETNAMEIDERR
32 RETPAGE 100 LOCKED
33 RTEFAIL 101 RECORDBUSY
34 RTESOME 102 UOWNOTFOUND
35 TSIOERR 103 UOWLNOTFOUND
36 MAPFAIL 104 LINKABEND
37 INVERRTERM 105 CHANGED
38 INVMPSZ 106 PROCESSBUSY
39 IGREQID 107 ACTIVITYBUSY
40 OVERFLOW 108 PROCESSERR
41 INVLDC 109 ACTIVITYERR
42 NOSTG 110 CONTAINERERR
43 JIDERR 111 EVENTERR
44 QIDERR 112 TOKENERR
45 NOJBUFSP 113 NOTFINISHED
46 DSSTAT 114 POOLERR
47 SELNERR 115 TIMERERR
48 FUNCERR 116 SYMBOLERR
49 UNEXPIN 117 TEMPLATERR
50 NOPASSBKRD 118 NOTSUPERUSER
51 NOPASSBKWR 119 CSDERR
52 SEGIDERR 120 DUPRES
53 SYSIDERR 121 RESUNAVAIL
54 ISCINVREQ 122 CHANNELERR
55 ENQBUSY 123 CCSIDERR
56 ENVDEFERR 124 TIMEDOUT
57 IGREQCD 125 CODEPAGEERR
58 SESSIONERR 126 INCOMPLETE
59 SYSBUSY 127 APPNOTFOUND
    128 BUSY
       
EIBRESP2
Contains more detailed information that can help explain why the RESP condition occurred. This field contains meaningful values, as documented with each command to which it applies. For requests to remote files, EIBRESP2 contains binary zeros. If a program uses DPL to link to a program in another CICS region, an EIBRESP2 from the remote region is not returned to the program doing the DPL.
For programs written in C or C++, any value passed via the exit or return function is saved in EIBRESP2. This means that when DPL is used to link to a C or C++ program in a remote region, this value is not returned to the linking program.
COBOL:     PIC S9(8) COMP.
C:         long int eibresp2;
PL/I:      FIXED BIN(31)
Assembler: F
EIBRLDBK
Indicates rollback.
COBOL:     PIC X(1).
C:         unsigned char eibrldbk;
PL/I:      CHAR(1)
Assembler: CL1
EIBRSRCE
Contains the symbolic identifier of the resource being accessed by the latest executed command as shown in Table 1
Table 1. Symbolic identifier of resource being accessed
Command type Resource Length
BMS Map name 7
File control File name 8
Interval control Transaction name 4
Journal control Journal number H
Journal control Journal name 8
Program control Program name 8
Temporary storage control TS queue name 8 or 16
Terminal control Terminal name; LU name; LU6.1 session or APPC convid 4
Transient data control TD queue name 4
Note:
  1. H= halfword binary.
  2. Identifiers less than eight characters in length are padded on the right with blanks.
  3. Identifiers greater than eight characters in length are truncated.
COBOL:     PIC X(8).
C:         char eibrsrce [8];
PL/I:      CHAR(8)
Assembler: CL8
EIBSIG
Indicates that SIGNAL has been received (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibsig;
PL/I:      CHAR(1)
Assembler: CL1
EIBSYNC
Indicates that the application program must take a sync point or terminate. Before either is done, the application program must ensure that any other facilities, owned by it, are put into the send state, or are freed (X'FF').
COBOL:     PIC X(1).
C:         unsigned char eibsync;
PL/I:      CHAR(1)
Assembler: CL1
EIBSYNRB
Indicates that the application program should issue a SYNCPOINT ROLLBACK command (X'FF'). This field is only set in application programs holding a conversation on an APPC or MRO link.
COBOL:     PIC X(1).
C:         unsigned char eibsynrb;
PL/I:      CHAR(1)
Assembler: CL1
EIBTASKN
Contains the task number assigned to the task by CICS. This number appears in trace table entries generated while the task is in control. The format of the field is packed decimal.
COBOL:     PIC S9(7) COMP-3.
C:         char eibtaskn [4];
PL/I:      FIXED DEC(7,0)
Assembler: PL4
EIBTIME
Contains the time at which the task is started (this field is updated by the ASKTIME command). The time is in packed decimal form (0HHMMSS+), and can contain a value in the range 0000000+ to 0240000+. Both 0000000+ and 0240000+ are valid.
COBOL:     PIC S9(7) COMP-3.
C:         char eibtime [4];
PL/I:      FIXED DEC(7,0)
Assembler: PL4
EIBTRMID
Contains the symbolic terminal identifier of the principal facility (terminal or logical unit) associated with the task.
COBOL:     PIC X(4).
C:         char eibtrmid [4];
PL/I:      CHAR(4)
Assembler: CL4
The following prefixes are used to identify intercommunication sessions, terminals, and devices:
Table 2. Standard prefixes for sessions, terminals, and devices
Prefix Session, terminal, or device
- APPC session
} Bridge facility
¬ Console
/ IPIC session
< or > MRO session
{ Remote terminal
\ (default system initialization VTPREFIX value) Virtual terminal
EIBTRNID
Contains the symbolic transaction identifier of the task.
COBOL:     PIC X(4).
C:         char eibtrnid [4];
PL/I:      CHAR(4)
Assembler: CL4