TSO-ISPF JCL COBOL VSAM DB2 CICS IMS-DB IMS-DC Tools Articles Forum Quiz Interview Q&A

Message Processing - Output


Once your application program has processed an input message, it will output a message to the device that originated the message. In this case, the application program will send a message to the message queue. To do this, the output message, like the input message, must follow a certain format.

Let's assume that our application program created a message to be sent back to the client. The general format of an output message is shown in Figure 4-11, and is defined as follows:

PL/I:

DCL 01 W_OUTPUT_MESSAGE,
              05 W_OM_LL,         FIXED BIN(31) INIT(??).
              05 W_OM_ZZ,         FIXED BIN(15) INIT(??).
              05 W_MESSAGE_TEXT;  CHAR(NNNN);

COBOL:

01 W-OUTPUT-MESSAGE.
      05  W-OM-LL         PIC  S9(4)  COMP VALUE  ???.
      05  W-OM-ZZ         PIC  S9(4)  COMP VALUE  ???.
      05  W-MESSAGE-TEXT  PIC  X(NNNN).

Format of an Output Message


Although it begins the same as that for an input message, the difference will be that we have many more fields to send back to the MFS for formatting. Remember that we are going to be sending attribute information to the screen (ATTR=YES on each MFLD of MOD).

Remember that for input messages, IMS calculated the LL and determined the ZZ. For output messages, the application program must provide IMS with a valid LL and a valid ZZ prior to sending the output message to the message queue.

Let's look at the MOD to review what fields we are going to send to the screen.

************************************************************************
* MESSAGE     OUTPUT     DESCRIPTOR (MOD)                              *
************************************************************************
ABCOSTAT MSG   TYPE=OUTPUT,SOR=(ABCSTA,IGNORE),OPT=1,PAGE=NO,          X
               NXT=ABCISTAT
         SEG
         MFLD (SYSDATE,DATE2)
         MFLD (SYSTIME,TIME)
         MFLD ITEMNUM,LTH=08,ATTR=YES
         MFLD STCODE,LTH=03,ATTR=YES
         MFLD STDTIN,LTH=08,ATTR=YES
         MFLD STDOUT,LTH=08,ATTR=YES
         MFLD STDESC,LTH=22,ATTR=YES
         MSGEND
         END

Based on this definition, we would define a detailed output area in our program as shown in Figure 4-12. Note that the output area specifies in the LL and ZZ valid values for each field.

PL/I:

DCL  01 W_OUTPUT_MESSAGE.
        05 W_OM_LL  FIXED BIN(31) INIT(53),
        05 W_OM_ZZ  FIXED BIN(15) INIT(1),
        05 W_OM_MESSAGE_TEXT,
           10 W_OM_ITEM_MFLD,
              15 W_OM_AITEM CHAR(02) INIT(' '),
              15 W_OM_ITEM  CHAR(06) INIT(' '),
           10 W_OM_STCODE_MFLD,
              15 W_OM_ASTATUS CHAR(02)INIT(' '),
              15 W_OM_STATUS  CHAR(01)INIT(' '),
           10 W_OM_STDTIN_MFLD,
              15 W_OM_ADATEIN CHAR(02)INIT(' '),
              15 W_OM_DATEIN  CHAR(06)INIT(' '),
           10 W_OM_STDTOUT_MFLD,
              15 W_OM_ADATEOUT CHAR(02)INIT(' '),
              15 W_OM_DATEOUT CHAR(06) INIT(' '),
           10 W_OM_STCESC_MFLD,
              15 W_OM_ADESC  CHAR(02)INIT(' '),
              15 W_OM_DESC 	 CHAR(20) INIT(' ');

COBOL:

01  W-OUTPUT-MESSAGE.
    05 W-OM-LL  PIC S9(4) VALUE +53 COMP.
    05 W-OM-ZZ  PIC S9(4) VALUE +1   COMP.
    05 W-OM-MESSAGE-TEXT.
       10 W-OM-ITEM-MFLD.
          15 W-OM-AITEM    PIC S9(4) VALUE +0   COMP.
          15 W-OM-ITEM     PIC X(06) VALUE ' '.
       10 W-OM-STDCODE-MFLD.
          15 W-OM-ASTATUS  PIC S9(4) VALUE +0   COMP.
          15 W-OM-STATUS   PIC X VALUE ' '.
       10 W-OM-STDTIN-MFLD.
          15 W-OM-ADATEIN  PIC S9(4) VALUE +0   COMP.
          15 W-OM-DATEIN   PIC X(06) VALUE ' '.
       10 W-OM-STDOUT-MFLD.
          15 W-OM-ADATEOUT PIC S9(4) VALUE +0   COMP.
          15 W-OM-DATEOUT  PIC X(06) VALUE ' '.
       10 W-OM-STDESC-MFLD.
          15 W-OM-ADESC    PIC S9(4) VALUE +0   COMP.
          15 W-OM-DESC     PIC X(20) VALUE ' '.

Message OUTPUT Area Definition


Let's review how this output area maps to the MOD.

W-OM-LLL:

This field specifies the length of the message. This is what tells IMS how much data to take from your program as a message. It must be a binary field because IMS will interpret the first two bytes as binary, (first four bytes in PL/1) in order to determine how much data to take from the application program. This must be the length of all the fields (minus 2 if PL/1), including the LL and the ZZ.

W-OM-ZZ:

This should contain the value 1 unless using advanced MFS device control features. (A value of 0 is treated by MFS as a 1.)

W-OM-AITEM:

This field represents the attribute bytes for the next field to follow in the message. In the MOD, it is included as part of the MFLD with DFLD ITEMNUM.

WOM-ITEM:

Item Number is a field on the screen. It is six bytes long. In the MOD, it is the last six bytes of the MFLD with label ITEMNUM.

W-OM-ASTATUS:

This field represents the attribute bytes for the next field to follow in the message. In the MOD, it is included as part of the MFLD with DFLD STCODE.

W-OM-STATUS:

Status Code is a field on the screen. It is one byte long. In the MOD, it is the last byte of the MFLD with DFLD STATUS.

W-OM-DATEIN:

This field represents the attribute bytes for the next field to follow in the message. In the MOD, it is included as part of the MFLD with DFLD STDTIN.

W-OM -DATEIN:

Status Date In is a field on the screen. It is six bytes long. In the MOD, it is the last six bytes Status Date In is a field on the screen. It is six bytes long. In the Mod, it is the last six bytes of the MFLD with DFLD STDTIN.

W-OM-ADATEOUT:

This field represents the attribute bytes for the next field to follow in the message. In the MOD, it is included as part of the MFLD with DFLD STDOUT.

W-OM-DATEOUT:

Status Date Out is a field on the screen. It is six bytes long. In the MOD, it is the last six bytes of the MFLD with DFLD STDTOUT.

W-OM-ADESC:

This field represents the attribute bytes for the next field to follow in the message. This field, plus the following field, combine to map to the last MFLD with DFLD label STDESC.

W-OM-DESC:

Status Description is a field on the screen. It is twenty bytes long. In the MOD, it is the last 20 bytes of the DFLD STDESC.

Note: The system date and time are not coded as part of the output message area in the program because they are inserted into the message by MFS when the MOD and DOF are combined to create the formatted screen.

If you have any doubts or queries related to this chapter, get them clarified from our Mainframe experts on IBMMainframer Community!

Are you looking for Job Change? Job Portal