MainframeSupports
tip week 5/2012:

Almost two years ago in week 12/2010 I wrote a tip about how to measure the CPU usage in a CICS program. Unfortunately this piece of code does not work any more if your CICS installation has been upgraded to CICS Transaction Server 3.2 or newer. In older versions of CICS my previous tip still works. Now I will show you a piece of code that works regardless of CICS version (except very old ones where COLLECT was not invented):

DATA DIVISION.
WORKING-STORAGE SECTION.
01  DFHMNTDS-POINTER POINTER.
01  WORKUSED PIC S9(9) BINARY.
01  LASTUSED PIC S9(9) BINARY.
01  CPUUSAGE PIC S9(9) BINARY.
LINKAGE SECTION.
01  DFHMNTDS-OLD.
  02  MNTLEN PIC S9(4) BINARY.
  02  FILLER PIC X(1262).
  02  CPUTIME-OLD PIC S9(9) BINARY.
01  DFHMNTDS-NEW.
  02  FILLER PIC X(1448).
  02  CPUTIME-NEW PIC S9(18) BINARY.
PROCEDURE DIVISION.
    ...
    MOVE 0 TO LASTUSED
    PERFORM CPU-SO-FAR
    ... ALL THE WORK I WANT TO MEASURE
    PERFORM CPU-SO-FAR
    DISPLAY 'MEASURED CPU CONSUMPTION IN 1/1000 SECONDS = ' CPUUSAGE
    ...
CPU-SO-FAR.
    EXEC CICS
      SUSPEND NOHANDLE
    END-EXEC
    EXEC CICS
      COLLECT STATISTICS SET(DFHMNTDS-POINTER)
      MONITOR(EIBTASKN) NOHANDLE
    END-EXEC
    IF EIBRESP = 0
      SET ADDRESS OF DFHMNTDS-OLD TO DFHMNTDS-POINTER
      IF MNTLEN < 2300
        COMPUTE WORKUSED = CPUTIME-OLD / 62,5
      ELSE
        SET ADDRESS OF DFHMNTDS-NEW TO DFHMNTDS-POINTER
        COMPUTE WORKUSED = CPUTIME-NEW / 4096000
      END-IF
      COMPUTE CPUUSAGE = WORKUSED - LASTUSED
      MOVE WORKUSED TO LASTUSED
    ELSE
      MOVE 0 TO WORKUSED
      MOVE 999999999 TO CPUUSAGE
    END-IF
    .

In comparison to the previous tip I have introduced an EXEC CICS SUSPEND as this command forces CICS to update CPU time. Using the earlier tip I sometime experienced a CPU time of zero being returned although I knew the the task had used a lot of CPU. SUSPEND fixed that. In CICS TS 3.2 the length of the DFHMNTDS-NEW area is about 2360 bytes long (may vary a bit on your installation) and I am pretty sure the corresponding area in CICS TS before 3.2 is less than 2300 bytes long. I use this length to test whether I should use the old or the new definition of DFHMNTS.

As an extra feature in CICS TS 3.2 the CPUTIME has been given the same precision as the CPU time in the ASCB. It is probably because of the less precise CPU time in earlier versions that it now has been changed. Unfortunately this change hurt my previous tip on the subject. On the other hand I can now confirm that CPUTIME includes all CPU time consumed by the task no matter how the transaction is configured.

Previous tip in english        Forrige danske tip        Tip list