Examples of invoking application naming EMPs
Figure 1 shows an assembler example of how to move a CICS® transaction ID to the transaction monitoring area.
DFHEISTG DSECT
EMPDATA1 DS F Data area for DATA1 address
*
*
* Constants for DATA2 (null value) and ENTRYNAME
*
EMPDATA2 DC F'0'
APPLNAME DC CL8'DFHAPPL'
*
LA Rn,tranid Set addr of tranid
ST Rn,EMPDATA1 Store tranid for EMP
EXEC CICS MONITOR POINT(1) ENTRYNAME(APPLNAME) C
DATA1(EMPDATA1) DATA2(EMPDATA2) NOHANDLE
This example shows 4 bytes of user data, typically the transaction ID, being moved using the DFHAPPL.1 EMP. The data starts at offset 0, and the data length defaults to the length specified in the application naming EMP in the MCT. In this example, CICS monitoring domain uses the default length defined in the MCT, because DATA2 is defined as a null value. For the DFHAPPL EMPs, CICS monitoring domain requires you to specify both DATA1 and DATA2.
Figure 2 shows a COBOL example of how to move a predefined application name and a transaction identifier to the transaction monitoring area. This example uses both EMP 1 and EMP 2 of the DFHAPPL EMPs, moving 4 bytes and 8 bytes respectively, which are the default lengths defined in the MCT.
IDENTIFICATION DIVISION.
PROGRAM-ID. APPLNAME.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
77 APPLICATION-NAME-PTR POINTER.
77 MENU-APPLICATION-NAME PIC X(4) VALUE 'MENU'.
77 PAYROLL-APPLICATION-NAME PIC X(8) VALUE 'PAYROLL '.
77 DFHAPPL-NAME PIC X(8) VALUE 'DFHAPPL '.
77 DFHAPPL-DATA2 PIC S9(8) COMP VALUE +0.
77 BLANKS PIC X VALUE SPACE.
*
LINKAGE SECTION.
77 LS-APPLICATION-NAME PIC X(8).
*
PROCEDURE DIVISION.
* Get storage for DFHAPPL data and set address
EXEC CICS GETMAIN FLENGTH(LENGTH OF LS-APPLICATION-NAME)
SET(APPLICATION-NAME-PTR) INITIMG(BLANKS)
END-EXEC.
SET ADDRESS OF LS-APPLICATION-NAME TO APPLICATION-NAME-PTR.
MOVE PAYROLL-APPLICATION-NAME TO LS-APPLICATION-NAME.
* Invoke DFHAPPL EMP 2 to add the application name
EXEC CICS MONITOR ENTRYNAME(DFHAPPL-NAME) POINT(2)
DATA1(APPLICATION-NAME-PTR) DATA2(DFHAPPL-DATA2)
NOHANDLE
END-EXEC.
* Re-use application data area for transaction ID
MOVE MENU-APPLICATION-NAME TO LS-APPLICATION-NAME.
* Invoke DFHAPPL EMP 1 to add the transaction ID
EXEC CICS MONITOR ENTRYNAME(DFHAPPL-NAME) POINT(1)
DATA1(APPLICATION-NAME-PTR) DATA2(DFHAPPL-DATA2)
NOHANDLE
END-EXEC.
SET ADDRESS OF LS-APPLICATION-NAME TO NULL.
EXEC CICS FREEMAIN DATAPOINTER(APPLICATION-NAME-PTR)
NOHANDLE
END-EXEC.
EXEC CICS RETURN END-EXEC.