IBM Support

PI60947: DOCUMENT Debug Tool Code Coverage Utility (DTCU) limitation of the DTCU breakpointing mechanism.

Subscribe

You can track all active APARs for this component.

 

APAR status

  • Closed as documentation error.

Error description

  • Debug Tool Code Coverage Utility (DTCU) limitation of the DTCU
    breakpointing mechanism.
    
    Some background:
    
    1) DTCU places either Short or Long SVC breakpoints at the
    beginning of each high level language statement (and in some
    cases inside them).
    
    2) A Short SVC breakpoint is used for 2 byte assembler
    instructions.
    
       A Long SVC breakpoint is used for 4 or 6 byte instructions.
    The Long SVC instruction carries some information with it that
    makes it easier to recognize at runtime.
    
    3) At runtime, when a breakpoint SVC is encountered, DTCU looks
    though all the active sessions for a 'pattern match' of this
    breakpoint and its surrounding breakpoints. The pattern match
    algorithm works best for Long SVC breakpoints. The pattern
    match algorithm can break down if a long sequence of Short SVC
    breakpoints is seen (since it can't tell one long sequence of
    Short SVC breakpoints from another).
    
    If you have long sequences of high level language code (such as
    COBOL) where the 1st assembler instruction for each high level
    language instruction is a short assembler instruction (2 byte
    versus 4 or 6 byte), this breakdown of the matching algorithm
    may be seen.
    
    
    The visible symptoms of this are shown in the example below:
    
    1. The execution counts can be off (all the MOVE statements
    should have the same execution count).
    
    2.  The annotation can be wrong (all the MOVE statements should
    be marked with a :).
    
         * SOME TABLES
          01 T1.
            05 TE1       PIC 9999   OCCURS 10 TIMES.
          01 T2.
            05 TE2       PIC 9999   OCCURS 10 TIMES.
          ...
          01 T10.
            05 TE10      PIC 9999   OCCURS 10 TIMES.
         * MORE STUFF
          01 STUFF.
            05 N         PIC  9(2)  COMP.
    
          PROCEDURE DIVISION.
    
         * CYCLE N 1 TO 10 AND PUT VALUE IN EACH TABLE.
     :        PERFORM WITH TEST AFTER                      >0001<
                      VARYING N FROM 1 BY 1 UNTIL N = 10
     &                IF N < 6 THEN                        >0010<
     :                  MOVE I1  TO TE1(N)                 >0005<
     :                  MOVE I2  TO TE2(N)                 >0005<
     :                  MOVE I3  TO TE3(N)                 >0005<
     :                  MOVE I4  TO TE4(N)                 >0005<
     :                  MOVE I5  TO TE5(N)             --> >0013<
     ^ <--              MOVE I6  TO TE6(N)             --> >0000<
     :                  MOVE I7  TO TE7(N)                 >0005<
     :                  MOVE I8  TO TE8(N)                 >0005<
     :                  MOVE I9  TO TE9(N)                 >0005<
     :                  MOVE I10 TO TE10(N)                >0005<
                      ELSE
                        ...
     :                  MOVE I1  TO TE10(N)                >0005<
                      END-IF
     &        END-PERFORM                                  >0010<
    
    
    If you looked at the generated code you might see something
    like:
    
     000063  MOVE
        0003DC  1F22                    SLR   2,2      <<- short BP
        0003DE  BF23 A1E8               ICM   2,3,488(10)
        0003E2  4C20 801A               MH    2,26(0,8)
        0003E6  1A2A                    AR    2,10
        0003E8  D203 204C A000          MVC   76(4,2),0(10)
        0003EE  96F0 204F               OI    79(2),X'F0'
     000064  MOVE
        0003F2  1F22                    SLR   2,2      <<- short BP
        0003F4  BF23 A1E8               ICM   2,3,488(10)
        0003F8  4C20 801A               MH    2,26(0,8)
        0003FC  1A2A                    AR    2,10
        0003FE  D203 2074 A008          MVC   116(4,2),8(10)
        000404  96F0 2077               OI    119(2),X'F0'
     000065  MOVE
        000408  1F22                    SLR   2,2      <<- short BP
        00040A  BF23 A1E8               ICM   2,3,488(10)
        00040E  4C20 801A               MH    2,26(0,8)
        000412  1A2A                    AR    2,10
        000414  D203 209C A010          MVC   156(4,2),16(10)
        00041A  96F0 209F               OI    159(2),X'F0'
    
    DTCU is going to put a breakpoint at the beginning of each
    COBOL source statement, in this case MOVE.  In this case it
    puts it on the
    
        0003DC  1F22                    SLR   2,2      <<- short BP
    
        0003F2  1F22                    SLR   2,2      <<- short BP
    
        000408  1F22                    SLR   2,2      <<- short BP
    
    and so forth and so on
    
    Now, a couple of things come into play:
    
    1) This is a 2 byte instruction  - so DTCU has to use its
    'short SVC' breakpoint.  Short SVC breakpoints are harder to
    'identify' at runtime by the pattern matcher.
    
    2) There are a lot of similar MOVE instructions in a row, which
    means we have a set of Short SVC breakpoints all together (in
    this particular piece of code, there are 10 of them in a row)
    so the pattern matcher's job just got harder.
    
    So, lots of COBOL statements in a row, all that start with a 2
    byte generated assembler instruction, leads to the pattern
    matcher, at runtime, mis-identifying some breakpoints and
    changing the execution count of the wrong instruction.
    
    If the generated assembler instruction was 4 or 6 bytes,  DTCU
    could have used its Long SVC breakpoint which keeps a random
    number for each breakpoint (and some additional info) and which
    be identified more accurately at runtime.
    
    
    This particular testcase is prone to this because of:
    
    1) its structure has long groups of MOVEs in certain places
    
    2) the MOVEs are all into a table ... so the generated code
    starts off with a similar calculation related to the index
    
    3) the index is short
    
            05 N         PIC  9(2)  COMP.
    
    4) the TRUNC(BIN) COBOL compiler option is used, which makes
    the compiler work extra hard to make sure only the proper
    number of digits are used in a calculation, and in this cases
    results in an SLR as the 1st instruction
    
    In this particular case, there might be a few workarounds
    
    IF TRUNC(OPT) or TRUNC(STD) (the default) was used, the SLR
    might change to a LH (which is 4 bytes long) and the problem
    would go away.  Also, if the index was declared as something
    that you needed a fullword or halfword to hold, again the SLR
    might change to an LH or L.
    So, those 2 things are a possible bypass -  declare the index
    to use at least a halfword of space or don't use TRUNC(BIN), If
    you tried that you would need to examine the generated code to
    see if the problem MOVEs started off with 4 byte assembler
    instructions (to guarantee that the problem had been bypassed).
    Note that with the variety of ways that a high level language
    compiler can generate code means that the above workaround may
    not work in every case.
    
    Note that the more modern code coverage function described in
    the User's Guide appendix "Appendix E.  Debug Tool Code
    Coverage" is not susceptible to this problem (but does not
    offer execution counts).
    

Local fix

Problem summary

  • Debug Tool Code Coverage Utility (DTCU) limitation of the
    DTCU breakpointing mechanism.
    

Problem conclusion

  • Users Guide needs to be expanded
    

Temporary fix

Comments

APAR Information

  • APAR number

    PI60947

  • Reported component name

    DEBUG TOOL Z/OS

  • Reported component ID

    5655Q1000

  • Reported release

    D10

  • Status

    CLOSED DOC

  • PE

    NoPE

  • HIPER

    NoHIPER

  • Special Attention

    NoSpecatt / Xsystem

  • Submitted date

    2016-04-19

  • Closed date

    2017-04-13

  • Last modified date

    2017-04-13

  • APAR is sysrouted FROM one or more of the following:

  • APAR is sysrouted TO one or more of the following:

Fix information

Applicable component levels

[{"Business Unit":{"code":"BU058","label":"IBM Infrastructure w\/TPS"},"Product":{"code":"SSTQWA","label":"IBM Debug for z\/OS"},"Component":"","ARM Category":[],"Platform":[{"code":"PF025","label":"Platform Independent"}],"Version":"D10","Edition":"","Line of Business":{"code":"LOB35","label":"Mainframe SW"}}]

Document Information

Modified date:
15 October 2020