Space announcement This documentation space provides the same content as before, but the organization of the content has changed. The content is now organized based on logical branches instead of legacy book titles. We hope that the new structure will help you quickly find the content that you need.

Analyzing program logic for COBOL


This section describes the built-in dynamic analysis features that let you identify program structure, trace the flow of control, monitor execution coverage, and review the execution path. These features assist you in understanding what the program does and how to reach a certain location in the program. The Code Debug TSO commands covered here are FIND, TRACE, SHOW PREVIOUS, COUNT, MONITOR, REVERSE, and RESUME.

If you have Code Debug Db2 Extension and File-AID for Db2, you can analyze how SQL statements execute with the EXPLAIN command. See Using Code Debug for Db2 Extension for more information.

Identifying Program Structure

The Code Debug TSO FIND command allows you to search data relationships and program structures, in addition to locating character strings. For instance, the FIND command can process data names and identify COBOL statements that directly or indirectly affect or see  the data names. COBOL-structure keywords such as ALTER, CONDITION, I/O, etc. are processed to query COBOL statements that have the potential to modify data, conditional constructs, and I/O statements. With the highlighting effect and the capability to suppress statements that do not qualify for the search category, the source display screen can turn into a representation of “data flow cross reference” and a “high-level structure.”

One example of the COBOL sensitivity of FIND is the ability to find data names, aliases and the use of the data name. Some of the keywords related to finding data names are:

DEFine

Data name is defined.

MODify

Value of the data name has changed or has the potential for change.

USE

Value of the data name is used, but not modified.

REFerence

Data name is defined, modified, or used.

The default is REFERENCE. When FIND is issued on a data name with no additional keywords, all references to the data name are found.

Finding All References for a Data Name

Enter the following command to find the data name SUBS:

FIND SUBS

Important

The SET KEEP MAX 5 command was used to suppress the Keep window when no keeps are explicitly requested, and the SET AUTOKEEP OFF command was used to turn off the display of automatically kept data for all the FIND examples shown in this section.

The response to the FIND SUBS command is illustrated in Result of Entering FIND SUBS. The message line indicates the number of times the data name SUBS is referenced in the program. There are 49 data references for SUBS: It is defined once, used 30 times, and modified 18 times. Each reference for the data name SUBS is highlighted and one of the following messages appear in the message area to the right of the found line: DEF, USE, or MOD.

Important

Defines will be found first. All defines are found in the Data Division because this is the section where the data names are defined. The uses and modifications of a data name will be found in the Procedure Division.

To find the next occurrence of SUBS, press PF5 or type FIND on the command line as shown in the following figure, move the cursor down past the line in which SUBS is defined, and press Enter.

Result of Entering FIND SUBS

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===> FIND                                               SCROLL ===> CSR
           49 Data Refs: 1 DEF, 30 USES, 18 MODS found for SUBS
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
000084    * SUBSCRIPT FOR INDEXING ALONG INPUT MESSAGE LINE ITEMS
000085    77  SUBS  PIC S9(3) COMP.                                         DEF
000087    * SUBSCRIPT FOR INDEXING ALONG SPA LINE ITEMS
000089    77  SPA-SUBS  PIC S9(3) COMP.
000090    *
000091    *            DL/I CALL FUNCTIONS
000092    *
000093    77  GU-FUNC     PIC X(4) VALUEGU  ’.
000094    77  GN-FUNC     PIC X(4) VALUEGN  ’.
000095    77  ISRT-FUNC   PIC X(4) VALUEISRT’.


The following figure shows the result of the repeat FIND. The DEF, MOD, and USE messages remain on the display until execution begins or a new FIND command is issued. Note that entry of a repeat FIND does not remove these messages.

Result of a Repeat FIND

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: IMSPROG2   MODULE: IMSPROG2  COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
000653             MOVE MSG12A TO OUT-MSG
000654        ELSE MOVE NEXT-SHIP-DETAIL TO SUBS                            MOD
000655             PERFORM UNPROTECT-SHIP-LINES
000656                UNTIL SUBS = 3.                                       USE
000657    UNPROTECT-SHIP-LINES.
000658        MOVE UNPROT-ATTR-NUM TO FE20SNR-ATTR (SUBS)                   USE
000659            FE20SDAT-ATTR (SUBS), SHIPSTAT-ATTR (SUBS).             2 USE
000660        MOVE UNPROT-ATTR-ALPH TO FE20SMET-ATTR (SUBS).                USE
000661        ADD 1 TO SUBS.                                                MOD
000662    CHANGE-ORDER.


The remaining keywords that relate to finding data names are the following two groups—ALIAS, NOREDEFINE, NOALIAS, and DIRECT and INDIRECT. They are defined here and illustrated in examples on the following pages.

ALIas

Other references (such as redefined or group level names) to the same storage location are found.

NORedefine

Other references (except redefines) to the same storage location are found.

NOAlias

Alias names are not found; default.

DIRect

Only direct references to the data name are found; default.

INDirect

All references to the data name, its aliases (if indicated), and all places a data value is passed to or from the data name and its aliases are found.

Finding Aliases of a Data Name

The data name N-CNTR has the aliases N-N-C, N-N-C-TABLE, and NAME-N-CNTR-TABLE. Enter the following command to find all aliases of the data name N-CNTR:

    FIND N-CNTR ALIAS

The result of this FIND command is shown in following figure, where N-N-C-TABLE and N-N-C are aliases of N-CNTR because they are both group data names under which N-CNTR is defined. NAME-N-CNTR-TABLE is an alias of N-CNTR because N-N-C-TABLE redefines NAME-N-CNTR-TABLE. That is, N-N-C, N-N-C-TABLE, and NAME-N-CNTR-TABLE all have the same storage location as N-CNTR, as seen in the Data Division.

Enter the command DOWN;FIND, so the screen will be scrolled before a repeat FIND is issued.

Result of Finding N-CNTR With DIRECT and ALIAS

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===> DOWN;FIND                                          SCROLL ===> CSR
           10 Data Refs: 4 DEFS, 6 MODS found for N-CNTR
------   -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000013    WORKING-STORAGE SECTION.
000014    01  NAME-N-CNTR-TABLE                                             DEF
000015        05  FILLER  PIC X(21)   VALUEEQUILATERAL TRIANGLES’.
000016        05  FILLER  PIC X(04).
000017        05  FILLER  PIC X(21)   VALUEISOCELES TRIANGLES’.
000018        05  FILLER  PIC X(04).
000019        05  FILLER  PIC X(21)   VALUESCALENE TRIANGLES’.
000020        05  FILLER  PIC X(04).
000021        05  FILLER  PIC X(21)   VALUEINVALID TRIANGLES’.
000022        05  FILLER  PIC X(04).
000023    01  N-N-C-TABLE             REDEFINES NAME-N-CNTR-TABLE.          DEF
000024        05  N-N-C               OCCURS 4 TIMES                        DEF
000025                                INDEXED BY TX.
000026            10  N-NAME          PIC X(21).
000027            10  N-CNTR          PIC 9(04).                            DEF
000028    01  OUT-OF-RECS             PIC X.
000029    01  TRIANGLE-TYPE           PIC 9.
000030    01  WORK-REC.
000031        05  SIDE-A              PIC 9(01).
000032        05  SIDE-B              PIC 9(01).


The display scrolls to show the uses and modifications of N-CNTR in the Procedure Division. When you look at the following figure, notice that the number of times N-CNTR is used and modified on the line is indicated on statement 42.

Scrolling to Modifications of N-CNTR

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------   -------------------------------------------- Before TRIMAIN/AMODE 24 <>
=====> B  PROCEDURE DIVISION.
000035     MAIN-PARA.
000036        PERFORM INIT-PARA.
000037        PERFORM ANALYZE-NEXT-REC
000038            UNTIL OUT-OF-RECS =Y’.
000039        PERFORM ENDING-PARA.
000040 A      GOBACK.
000041    INIT-PARA.
000042        MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4)   4 MOD
000043        OPEN INPUT INFILE.
000045    ANALYZE-NEXT-SEC.
000046        READ INFILE INTO WORK-REC
000047           AT END
000048           MOVEYTO OUT-OF-RECS.
000049        IF OUT-OF-RECS =N
000050           MOVE ZERO TO TRIANGLE-TYPE
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE
000052           SET TX TO TRIANGLE-TYPE
000053           ADD 1 TO N-CNTR (TX).                                      MOD


Finding Indirect References to a Data Name

In all of the examples that have been discussed so far, the FIND default of DIRECT was used. When INDIRECT is specified for a data name, all statements directly or indirectly affected by the data name are found. The following example illustrates how INDIRECT is used and the results.

A good way to view indirect references is to use the EXCLUDE keyword with the FIND command. The EXCLUDE keyword excludes from view all lines that were not found. For example, issue the following command for the data name IN-PASS1:

   FIND IN-PASS1 IND X

The results of this FIND command are shown in the following figure where all references to IN-PASS1 are displayed. To display the next level of indirect references, enter FIND INDIRECT or press the PF17 key.

Finding IN-PASS1 INDIRECT With EXCLUDE

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===> FIND IND                                           SCROLL ===> CSR
                3 Data Refs:  1 DEF, 2 USES found for IN-PASS1
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
********************************** TOP OF MODULE ******************************
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 221 LINES NOT DISPLAYED
000232      02  IN-PASS1      PIC X(16).                                    DEF
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 336 LINES NOT DISPLAYED
000574              MOVE IN-PASS1 TO SE0ORDR1                               USE
- - - - - - - - - - - - - - - - - - - - - - - - - - - -  27 LINES NOT DISPLAYED
000604         MOVE IN-PASS1 TO SE0ORDR1                                    USE
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 385 LINES NOT DISPLAYED
******************************** BOTTOM OF MODULE ******************************


Each time FIND INDIRECT is entered, a new level of indirect references is found. When you look at the following figure, notice that SE0ORDR1 references are highlighted.

FIND INDIRECT - First Level of Indirection

------------------------------ CODE DEBUG TSO - SOURCE --------------------------
COMMAND ===>                                                    SCROLL ===> CSR
         7 Data Refs:  1 DEF, 2 USES, 4 MODS found for IN-PASS1
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
********************************** TOP OF MODULE ******************************
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 221 LINES NOT DISPLAYED
000232        02  IN-PASS1      PIC X(16).
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 109 LINES NOT DISPLAYED
000343    01  SE0ORDR1.                                                     DEF
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 226 LINES NOT DISPLAYED
000574              MOVE IN-PASS1 TO SE0ORDR1                               MOD
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000577                      MOVE SE0ORDR1 TO SPA-PASS1,                     USE
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 3 LINES NOT DISPLAYED
000582              MOVE SPA-PASS1 TO SE0ORDR1                              MOD
- - - - - - - - - - - - - - - - - - - - - - - - - - - -  20 LINES NOT DISPLAYED
000604          MOVE IN-PASS1 TO SE0ORDR1                                   MOD
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000607                  MOVE SE0ORDR1 TO SPA-PASS 1,                        USE
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000611          MOVE SPA-PASS1 TO SE0ORDR1                                  MOD
******************************* BOTTOM OF MODULE ******************************


When FIND INDIRECT (PF17) is entered again, all references to IN-PASS1, SE0ORDR1, and SPA-PASS1 are found (See the following figure).

FIND INDIRECT - Second Level of Indirection

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                    SCROLL ===> CSR
          5 Data Refs:  1 DEF, 2 USES, 2 MODS found for IN-PASS1
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
********************************** TOP OF MODULE ******************************
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 221 LINES NOT DISPLAYED
000232        02  IN-PASS1      PIC X(16).
- - - - - - - - - - - - - - - - - - - - - - - - - - - -  60 LINES NOT DISPLAYED
000293        02  SPA-PASS1                                                 DEF
- - - - - - - - - - - - - - - - - - - - - - - - - - - -  48 LINES NOT DISPLAYED
000343    01  SE0ORDR1.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - 226 LINES NOT DISPLAYED
000574              MOVE IN-PASS1 TO SE0ORDR1
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000577                      MOVE SE0ORDR1 TO SPA-PASS1,                     MOD
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 3 LINES NOT DISPLAYED
000582              MOVE SPA-PASS1 TO SE0ORDR1                              USE
- - - - - - - - - - - - - - - - - - - - - - - - - - - -  20 LINES NOT DISPLAYED
000604          MOVE IN-PASS1 TO SE0ORDR1
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000607                  MOVE SE0ORDR1 TO SPA-PASS1,                         MOD
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - 2 LINES NOT DISPLAYED
000611          MOVE SPA-PASS1 TO SE0ORDR1                                  USE
******************************* BOTTOM OF MODULE *******************************


When no more levels of indirect references are found, the following message is displayed in the message line:

   END OF INDIRECT SEARCH

Enter END (PF3) to reset all excluded lines in your program.

Important

The EXCLUDE keyword can be used on any FIND command. When it is used, Code Debug TSO excludes all lines before executing the FIND.

Finding COBOL Structures

FIND is also able to find COBOL structures using keywords in place of a character string. When a COBOL-structure keyword is entered instead of a data name, Code Debug TSO highlights all lines in the program where the COBOL structure is used.

Important

Currently, EXEC SQL WHENEVER and EXEC SQL DECLARE statements are not found when you issue the FIND SQL command.

The COBOL-structure keywords are listed as follows. See COBOL-Structure Keywords for descriptions and source relationships.

ALTer   CICS      INput   PARAgraph
BRAnch  CONDition IO      SQL
CALL    DLI       OUTput

Using FIND With the COBOL-Structure INPUT

Enter the following command to find all INPUT statements in the IQTEST program:

   FIND INPUT

The first input statement found is a READ statement, as shown in the following figure. The line that contains the input verb is highlighted. If the verb statement extends over multiple lines, multiple lines are highlighted, as shown. To locate the next input statement, press PF5 (repeat FIND).

Result of FIND With COBOL-Structure Keyword INPUT

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===> FIND                                               SCROLL ===> CSR
                             2 INPUT found
------   --------------------------------------------- Before IQTEST/AMODE 24 <>
=====> B  PROCEDURE DIVISION.
000131     A000-CREATE-IQ-TEST-REPORT.
000132        OPEN INPUT               IQ-TEST-FILE
000133             OUTPUT              IQ-TEST-REPORT-FILE.
000134        READ IQ-TEST-FILE
000135             AT END
000136                MOVENOTO ARE-THERE-MORE-RECORDS.
000137        MOVE IN-SCHOOL-NO TO INPUT-IQ.
000138        IF THERE-IS-A-RECORD


The next input statement is also a READ statement as shown in the following figure.

Result of a Repeat FIND for INPUT Keyword

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: IQTEST      MODULE: IQTEST   COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------   --------------------------------------------- Before IQTEST/AMODE 24 <>
000199             MOVE SPACES TO DETAIL-LINE.
000200             READ IQ-TEST-FILE
000201                AT END
000202                   MOVENOTO ARE-THERE-MORE-RECORDS.
000203    B005-PROCESS-DETAIL-RECS-EXIT.


When you enter FIND and no more INPUT statements are found, the following message is displayed in the message area:

   BOTTOM OF DATA REACHED

The input statements remain highlighted until execution begins or a new FIND command is issued.

Using FIND With the COBOL-Structure DLI and EXCLUDE Keywords

In this example, the FIND command is entered with the DLI and EXCLUDE keywords. The DLI keyword finds not only all lines in the OSDLI program that say EXEC DLI, but in each case, the entire DLI statement. The EXCLUDE keyword displays only the lines containing the requested information; all other lines are excluded from display. Enter the following command:

   FIND DLI X

When you look at the following figure, you can see at a glance where the DLI statements are, what types they are, and all parameters on each statement.

Result of FIND DLI With EXCLUDE

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===> NOL                                                SCROLL ===> CSR
PROGRAM: OSDLI       MODULE: OSDLI    COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------   ---------------------------------------------- Before OSDLI/AMODE 24 <>
******************************** TOP OF MODULE ********************************
- - -  - - - - - - - - - - - - - - - - - - - - - - - -  191 LINES NOT DISPLAYED
000201        EXEC DLI SCHD
000202             PSB(TRIDATA)
000203        END-EXEC.
- - -  - - - - - - - - - - - - - - - - - - - - - - - -   46 LINES NOT DISPLAYED
000256        EXEC DLI GET UNIQUE
000257                             SEGMENT(VALID) SEGLENGTH(4)
000258                             INTO(WORK-ROOT-SEG)
000259                             KEYS(WT-KEY-SEND) KEYLENGTH(2)
000260                             KEYFEEDBACK(WT-KEY-FEEDBACK)
000261                 END-EXEC.
- - -  - - - - - - - - - - - - - - - - - - - - - - - - - 20 LINES NOT DISPLAYED
000289        EXEC DLI
000290                 GET NEXT IN PARENT
000291                                        SEGMENT(VALID)
000292                                        SEGMENT(COUNT) SEGLENGTH(8)
000293                                        INTO(WORK-COUNT-SEG)
000294                                        KEYS(WT-KEY-SEND) KEYLENGTH(5)
000295                                        KEYFEEDBACK(WT-KEY-FEEDBACK)


Now, you must enter a NOLINES command to eliminate the message line xx LINES NOT DISPLAYED from the display. As illustrated in the following figure, the resulting display can now accommodate additional found lines.

Result of Issuing the NOLINES Command

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                    SCROLL ===> CSR
                              16 DLI found
------   ---------------------------------------------- Before OSDLI/AMODE 24 <>
******************************** TOP OF MODULE *********************************
000201        EXEC DLI SCHD
000202             PSB(TRIDATA)
000203        END-EXEC.
000256        EXEC DLI GET UNIQUE
000257                             SEGMENT(VALID) SEGLENGTH(4)
000258                             INTO(WORK-ROOT-SEG)
000259                             KEYS(WT-KEY-SEND) KEYLENGTH(2)
000260                             KEYFEEDBACK(WT-KEY-FEEDBACK)
000261                 END-EXEC.
000289        EXEC DLI
000290                 GET NEXT IN PARENT
000291                                        SEGMENT(VALID)
000292                                        SEGMENT(COUNT) SEGLENGTH(8)
000293                                        INTO(WORK-COUNT-SEG)
000294                                        KEYS(WT-KEY-SEND) KEYLENGTH(5)
000295                                        KEYFEEDBACK(WT-KEY-FEEDBACK)
000296                          END-EXEC.
000297        EXEC DLI
000298             REPLACE


Finding a String IN COBOL Structures

COBOL-structure keywords can also be used with the IN keyword. They are used to find a string or a data name IN a COBOL structure. For example, the following FIND command is entered with the string B010, part of a performed paragraph label:

   FIND B010 IN PARA

The FIND string IN COBOL-structure lets you focus on the statement that is of concern, rather than issue several repeat FIND commands. See the results illustrated in the following figure.

Result of FIND Data String With IN PARAGRAPH

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
                         1 CHARSB010FOUND
------   --------------------------------------------- Before IQTEST/AMODE 24 <>
000203    B005-PROCESS-DETAIL-RECS-EXIT.
000204    B010-PROCESS-TEACHER-CHANGE.
000205        DIVIDE TOTAL-TEACHER-IQ BY TEACHER-STUDENT-TOTAL
000206            GIVING WA-TCHR-AVG-IQ ROUNDED.
000207        MOVE WA-TCHR-AVG-IQ TO TATL-AVG-IQ.
000208        MOVE DOUBLE-SPACING TO PROPER-SPACING.
000209        WRITE IQ-TEST-REPORT-LINE FROM TEACHER-AVG-TOTAL-LINE
000210             AFTER PROPER-SPACING.
000211        MOVE ZERO TO TOTAL-TEACHER-IQ.
000212        MOVE ZERO TO WA-TCHR-AVG-IQ.
000213        MOVE ZERO TO TEACHER-STUDENT-TOTAL.


The NOLINES Keyword and Command

In the previous example, the NOLINES command was entered to suppress the xxx LINES NOT DISPLAYED message line that appears when the EXCLUDE keyword is used with FIND. A NOLINES keyword is also available with FIND. Like the NOLINES command, the NOLINES keyword eliminates the message line that appears with the use of the EXCLUDE keyword. However, it is effective only when used in conjunction with the EXCLUDE keyword.

Using the EXCLUDE Command With FIND

The EXCLUDE command includes the keyword parameter ALL, which excludes all lines in a program. The EXCLUDE ALL command can be used effectively with FIND.Issuing the EXCLUDE ALL command results in the removal of all the source lines in the display. You can also use the NOLINES command to suppress the xxx LINES NOT DISPLAYED message line.

Entering the following commands results in the display shown in Result of following figure:

   EXCLUDE ALL;NOLINES

After all lines in the program have been excluded, the FIND command can be issued for multiple data names, to make a cumulative search for the source of a problem.

Result of Excluding ALL Lines

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===> FIND SUBS                                          SCROLL ===> CSR
PROGRAM: IMSPROG2   MODULE: TRIMAIN   COMP DATE: 09/28/1996  COMP TIME: 12:54:26
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
******************************** TOP OF MODULE *********************************

****************************** BOTTOM OF MODULE ********************************


Note that you can also concatenate the EXCLUDE ALL command along with a FIND command. For example, entering the following commands results in the display shown in the following figure:

   EXCLUDE ALL;NOLINES;FIND SUBS

Result of FIND SUBS Command After EXCLUDE ALL Command

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                    SCROLL ===> CSR
          49 Data Refs: 1 DEF, 30 USES, 18 MODS found for SUBS
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
********************************* TOP OF MODULE ********************************
000085    77  SUBS  PIC S9(3) COMP.                                        DEF
000654        ELSE MOVE NEXT-SHIP-DETAIL TO SUBS                           MOD
000656                UNTIL SUBS = 3.                                      USE
000659        MOVE UNPROT-ATTR-NUM TO FE20SNR-ATTR (SUBS)                  USE
000660            FE20SDAT-ATTR (SUBS), SHIPSTAT-ATTR (SUBS).            2 USE
000661        MOVE UNPROT-ATTR-ALPH TO FE20SMET-ATTR (SUBS).               USE
000662        ADD 1 TO SUBS.                                               MOD
000680            THEN MOVE NEXT-SHIP-DETAIL TO SUBS.                      MOD
000681            PERFORM SHPCRTN UNTIL SUBS = 3 OR                        USE
000682                IN-SHIP-DETAIL (SUBS) = SPACES                       USE
000697        MOVE IN-SHIP-DETAILS (SUBS) TO SE0ORDR7.                     USE
000707        IF SUBS = 2                                                  USE


Using the FIND CSR Command

The CSR keyword issues a FIND command for the data name or string under the cursor. It functions like PEEK CSR, searching for data names as well as strings. IN and OF qualifications are automatically picked up.

When you look at the following figure, the cursor is positioned on the first M on line 553. Press the PF14 key or enter the FIND CSR command as shown.

Using the FIND CSR Command

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===> FIND CSR                                          SCROLL ===> CSR
PROGRAM: IMSPROG2   MODULE: IMSPROG2  COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
000548        ACCEPT TODAY FROM DATE.
000549        MOVE CORR TODAY TO TODAY1.
000550        MOVE CORR TODAY TO TODAY2.
000551   *             CALCULATE ABOUT 2 WEEKS HENCE INTO TODAY2
000552        IF DD OF TODAY2 < 15, ADD 14 TO DD OF TODAY2.
000553        ELSE ADD 1 TO MM OF TODAY2, SUBTRACT 14 FROM DD OF TODAY2.
000554        IF MM OF TODAY2 = 13, MOVE 01 TO MM OF TODAY2
000555            ADD 1 TO YY OF TODAY2


FIND CSR searches for the first instance of the data name under the cursor and highlights it, as shown in the following figure.

Result of Entering FIND CSR

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                    SCROLL ===> CSR
            4 Data Refs: 1 DEF, 2 USES, 1 MOD found for MM
------   ------------------------------------------- Before IMSPROG2/AMODE 24 <>
000221    01  TODAY2.
000222        02  MM      PIC 99.                                          DEF
000223        02  DD      PIC 99.
000224        02  YY      PIC 99.
000225   *
000227   *         INPUT DATA FOR TRANSACTION TQ2CONEW
000228   *
000229    01  INPUT-MESSAGE-PASS1.
000230        02  IN-LL1          PIC  S9(3) COMP.
000231        02  IN-ZZ1          PIC  S9(3) COMP.
000232        02  IN-PASS1        PIC  X(16).
000233        02  FILLER          PIC  X(620).


Logging the Results of a FIND Command

Results of Data Name and COBOL Structure FINDs can optionally be written to the session log. Since this option defaults to OFF, a user must enter the SET command as follows to activate this feature:

   SET LOG FIND ON

Information written to the session log includes the FIND command entered, the name of the program being searched, the number of occurrences detected, and the source lines containing the argument. For all indirect FINDs and enhanced FINDs, the level of indirection is also logged.

All source statements containing the argument are displayed after the initial command has been issued, regardless whether the NEXT, PREV, LAST, or FIRST keywords are used. No additional logging will occur when a repeat FIND command is issued. Caution should be used when the FIND command is frequently issued, with explicit attention given to the amount of space allocated to the session log file.

The general format of the logged data can be seen in the following example (see the following figure):

Data Format When Logging the Results of a FIND Command

********************************* TOP OF DATA **********************************
+------------------------------------------------------------------------------+
:                                                              JOB: USER123    :
: XPEDITER/TSO RELEASE 06.40.00       CUSTOMER # 010000       STEP: TSOSTEP1   :
: TAPE CREATE DATE 1997050                                    DATE: 03/08/1997 :
: COMPUWARE CORPORATION                                       TIME: 15.16.19   :
+------------------------------------------------------------------------------+
  XPED TSO SPF
  TEST TRIMAIN
*** TRIMAIN  FROM USER!.LOADLIB                                  LINK 01/23/1997
  BEFORE TRIMAIN::TRIMAIN:
  AFTER  TRIMAIN::TRIMAIN:
  PAUSE Before TRIMAIN
  BEFORE BREAKPOINT ENCOUNTERED
  SET LOG FIND ON
  FIND TRIANGLE-TYPE
  PROGRAM=TRIMAIN

4 DATA REFS: 1 DEF, 1 USE, 2 MODS FOUND FOR TRIANGLE-TYPE
000029    01  TRIANGLE-TYPE           PIC 9.                              DEF
000050           MOVE ZERO TO TRIANGLE-TYPE                               MOD
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE               MOD
000052           SET TX TO TRIANGLE-TYPE                                  USE
******************************** BOTTOM OF DATA *******************************


Tracing the Flow of Control

You can trace the flow of control with the TRACE and the SHOW PREVIOUS commands.

Using the TRACE Command

The TRACE command traces the flow of control as your program executes and lets you view it on the Source display screen. The specified statements or paragraph names are highlighted as they are executed, until a breakpoint is reached, an abend is intercepted, a terminal I/O is issued, a keyboard interrupt is detected, or the end of the program is encountered.

In the case of tracing module calls, however, the tracing is not visible on the source screen. The calling module, the called module, and the number of times the calls are made are written to the session log during program execution. The call activities can be viewed by entering LOG and reviewing the session log.

For example, suppose you enter the following TRACE command for the TRIMAIN program:

TRACE MODULES

After you have executed the program by entering GO, you can access the session log using the LOG command. As seen in the following figure, you can trace the flow of control as the various modules are called.

Session Log for the TRACE MODULES Command

------------------------------- CODE DEBUG TSO - LOG --------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------------------------------------------------------ After TRIMAIN/AMODE 24 ->
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -        5 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -        6 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -        7 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -        8 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -        9 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -       10 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -       11 CALLS
TRITST RETURN TO TRIMAIN
TRITST CALLED BY TRIMAIN  -       12 CALLS
TRITST RETURN TO TRIMAIN
PAUSE AFTER TRIMAIN IN MAIN-PARA
TEST COMPLETED
******************************* BOTTOM OF DATA *********************************


When the TRACE command is used with the MAX keyword, the trace function pauses when execution reaches the preset limit. The default value for the maximum limit is 25. For additional information regarding the TRACE command see Using the TRACE Command.

Using the SHOW PREVIOUS Command

The SHOW PREVIOUS command lists, in logical sequence, the previous 100 statements along with the executed breakpoints. The list presented by the SHOW PREVIOUS command can be useful in reviewing the execution path to understand how you got to the present location. Since any implied breakpoints are recognized with the SHOW PREVIOUS command, a program that was run with the TRACE ALL PARAGRAPHS command presents a list like that shown in the following figure as the result of entering SHOW PREVIOUS.

Result of Entering the SHOW PREVIOUS Command

------------------------------- CODE DEBUG TSO - SHOW -------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 09/28/1996  COMP TIME: 14:41:59
------------------------------------------------------ After TRIMAIN/AMODE 24 ->
********************************* TOP OF DATA **********************************
000034   PROCEDURE DIVISION.                                           TRIMAIN
000035   MAIN-PARA.                                                    TRIMAIN
000041   INIT-PARA.                                                    TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000045   ANALYZE-NEXT-REC.                                             TRIMAIN
000054   ENDING-PARA.                                                  TRIMAIN
000040        GOBACK.                                                  TRIMAIN
****************************** BOTTOM OF DATA **********************************


Monitoring Execution Coverage

You can monitor execution coverage with the COUNT and SHOW COUNT commands.

Using the COUNT Command

The COUNT command maintains execution counts and lets you analyze statement level execution coverage after running the program. The following figure shows the result of setting counters at every paragraph by entering the following command, then pressing PF12 (GO) to resume execution:

   COUNT ALL PARAGRAPHS

Result of Entering the COUNT ALL PARAGRAPHS and GO Commands

------------------------- CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                  SCROLL ===> CSR
                               TEST COMPLETED
        ** END **




------   ------------------------------------------- After TRIMAIN/AMODE 24 <>
000035 B  PROCEDURE DIVISION.
000036     MAIN-PARA.                                                   0000001
000037        PERFORM INIT-PARA.
000038        PERFORM ANALYZE-NEXT-REC
000039            UNTIL OUT-OF-RECS = 'Y'.
000040        PERFORM ENDING-PARA.
====>> A      GOBACK.
000042    INIT-PARA.                                                    0000001
000043        MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4).
000044        OPEN INPUT INFILE.
000045        MOVE 'N' TO OUT-OF-RECS.
000046    ANALYZE-NEXT-REC.                                             0000014
000047        READ INFILE INTO WORK-REC
000048           AT END
000049           MOVE 'Y' TO OUT-OF-RECS.


A 7-digit counter is displayed at the right of the screen for each statement or paragraph that is counted. You can globally monitor execution coverage by using the ALL keyword or selectively monitor by specifying the statement numbers. When the ALL keyword is issued, however, it only applies to the current module.

Using the SHOW COUNT Command

The statements that are monitored with the COUNT command can be listed by entering the SHOW COUNT command. The source lines without counters are excluded from the screen display. The following figure illustrates the result of the SHOW COUNT command after monitoring execution coverage at the paragraph level.

Result of Entering the SHOW COUNT Command

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                    SCROLL ===> CSR
         SPECIFIED STATEMENTS NOT EXCLUDED - RESET WITHEND
        ** END **



------   --------------------------------------------- After TRIMAIN/AMODE 24 <>
******************************** TOP OF MODULE *********************************
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - - -  34 LINES NOT DISPLAYED
000035     MAIN-PARA.                                                    0000001
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - - - - 5 LINES NOT DISPLAYED
000041    INIT-PARA.                                                     0000001
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - - - - 3 LINES NOT DISPLAYED
000045    ANALYZE-NEXT-REC.                                              0000014
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - - - - 8 LINES NOT DISPLAYED
000054    ENDING-PARA.                                                   0000001
-  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - - - - 2 LINES NOT DISPLAYED
******   ********************* BOTTOM OF MODULE ********************************


When the SHOW COUNT command is issued, the entire Procedure Division is written to the session log with the 7-digit counters displayed.

If you do not want to write the entire Procedure Division to the session log, enter the SHOW COUNT command with the NOLOG keyword. The results of execution coverage will not be recorded.

Monitoring and Reviewing the Execution Path

The MONITOR and REVERSE commands are used to activate review mode. Review mode lets you monitor and review the execution path by stepping backwards through your program. You can view the statements that were executed during normal (forward) execution. You can trace backwards through the actual sequence of instructions that led to the current breakpoint and see the data values as they were at the time. There is no guesswork about which of the possible paths the program took; the actual path that was taken during forward execution of the program is displayed.

The MONITOR command records the execution history and the REVERSE command enables you to review the execution history.

To activate review mode, enter the MONITOR command from the primary command line. MONITOR without a module name records history for the current module—not necessarily the active module that is currently executing, but the module indicated by the program field on the third line.

After issuing the MONITOR command, execute the statements you want to review. Then, when your program pauses during logical execution, enter the following primary command:

   REVERSE

The REVERSE command places the execution arrow on the last statement that was executed, and changes the execution direction of your program—from forward to reverse (backward). From this point on, the REVERSE command acts as a toggle that changes the direction in which your program is executed. During review mode, the execution status message on the fourth line of the screen indicates the execution direction and the statement where execution is paused.

Important

Entering the REVERSE command only changes the direction of execution; it does not cause execution to occur.

You must enter the GO n or GO command to begin execution in the current direction.

The GO n command moves the active arrow n lines in the current direction, which lets you step through the program line-by-line. Unlike normal execution mode, a GO n command in review mode ignores module boundaries and will pause after executing n statements, regardless of what modules they are in. It is recommended that you use GO 1 commands to do a backward line-by-line execution.

In review mode, TRACE does not recognize the default maximum limit of 25 statements, and continues execution until it encounters the AT INITIAL EXECUTION POSITION. To halt the reverse trace, press the Attn key.

While review mode is activated, you can set and remove breakpoints, perform tracing (in either direction), and display data. For example, you may want to open a Keep window to view the data values as they are restored to their original state as reverse execution is performed, as shown in the following figure for the data value WORK-REC.

Review Mode with a Keep Window Opened

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
             NEXT LOGICAL INSTRUCTION IS RESUME EXECUTION
                                                    ---
000030 K 01 WORK-REC                              >  345
        ** END **

------   -------------------------------- Reverse - After TRIMAIN:45/AMODE 24 <>
000044        MOVENTO OUT-OF-RECS.
====>> A  ANALYZE-NEXT-REC


Important

While in review mode, you cannot use the GOTO command or alter data by typing over it or by using the MOVE command. Also, skipped lines are ignored during review mode.

To exit from review mode when you have finished doing your analysis, use the RESUME command.

The message AT CURRENT EXECUTION POSITION is displayed, and review mode is automatically ended. Normal forward execution occurs until you again enter the REVERSE command. You can also terminate review mode while in forward execution by entering GO or GO n until you see the message AT CURRENT EXECUTION POSITION.

Kept items are logged at each breakpoint while in review mode, just as in normal execution mode. The logged items are all logged independently of review mode or normal execution mode, except for the following:

  • Encountering the beginning of the program while in review mode
  • Encountering the current execution location while in review mode.

 

Tip: For faster searching, add an asterisk to the end of your partial query. Example: cert*