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.

Quick sample debugging session with COBOL


This section demonstrates some of the basic interactive debugging features of Code Debug TSO, using the sample program TRIMAIN, which calls TRITST and TRIRPT. This quick overview shows you how to do the following:

  • Prepare the programs
  • Start an interactive debugging session
  • Set breakpoints
  • Display file information
  • Display data values
  • Debug subroutines
  • Analyze data flow
  • Trace logic flow
  • Monitor and review the execution path.

Preparing the Programs

The source for TRIMAIN, TRITST, TRIRPT, and TRIDATA (the input data set containing the data) is provided in the SLXTSAMP library. The common load module, DDIO data set, test data, and file list libraries should have already been created and/or verified by your site installer. Contact your installer for the names of these libraries and data sets.

If these data sets and libraries were not created, you must compile and link-edit the programs using the Common Shared Services (CSS) COBOL language processor. You must also specify the appropriate load module on the Setup screen.

Option 1 on the Code Debug TSO Primary Menu can be used to compile and link-edit the programs. See Preparing Your Programs if you need assistance.

When you are ready to start the session, do the steps listed following steps.

Starting the Debugging Session

  1. Type TRIMAIN in the Profile field on the Code Debug TSO Primary Menu. Code Debug creates a profile for the session, displays the Profile screen, and prompts you to enter a description for the new profile. Type XPEDITER Sample Program TRIMAIN in the description area and press the End key. The Primary Menu is redisplayed.
  2. Type 2 (TSO) in the command line of the Primary Menu. The Environments Menu is displayed if this is your first time invoking a Code Debug TSO debugging session. Otherwise, the last environment test screen you used is displayed. To access the Environments Menu, type SETUP in the command line of the displayed environment test screen. Then type option 0 on the Test Setup Menu to display the Environments Menu.
  3. Type 1 (STANDARD) on the Environments Menu.
  4. Type SETUP on the Standard test screen.
  5. Type 1 (LOADLIBS) on the Setup Menu.
  6. On the Load Module Libraries screen, enter the name of the application load library that contains the TRIMAIN load module (optional).
  7. Press Enter.
  8. Type 2 (DDIO) on the Setup Menu.
  9. On the DDIO Files screen, you may enter the DDIO data set name that contains the source listing member of TRIMAIN. In addition to the original DDIO data set name, you may also specify a Shared Directory data set name and/or an LP database data set name.
  10. Press Enter.
  11. Type END or press PF3 to return to the Standard environment test screen.
  12. Specify the name of the program and the name of the file list or the JCL containing the names of the files required by your program. Complete the screen as shown in the following figure.

    Standard Test Screen 

    Profile: DEFAULT ---------------  STANDARD (2.1)  -----------------------
    COMMAND ===>

    COMMANDS:  SEtup (Display Setup Menu)
               PROFile (Display Profile Selection)
    TEST SELECTION CRITERIA:

                   Program ===> TRIMAIN
               Entry Point ===>
               Load Module ===>

            Initial Script ===>
               Post Script ===>

      PARM  ( Caps = YES ) ===>

      File List/JCL Member ===>
            Preview Files? ===> NO
       Code Coverage Test? ===> NO   (YES, NO, TDO)  SYSTEM FLOW? ===> NO
       Is This a DB2 Test? ===> NO    Plan ===>            System ===>

               Press ENTER to process  or  enter END command to terminate

  13. Press Enter to begin the Code Debug TSO debugging session. The message area contains the lines Allocating XPEDITER/TSO Data sets, then Allocating User Data sets. On a blank screen, the message Entering XPEDITER/TSO Test Environment appears.

Code Debug TSO processes the file list, allocates the necessary data sets, loads the program TRIMAIN, and displays the COBOL source listing. You should be able to see the message Before Breakpoint Encountered with the execution arrow (=====>) pointing to the PROCEDURE DIVISION statement. This means that TRIMAIN stopped before beginning execution of the program. Also, a left/right scroll indicator (e.g., -- Before TRIMAIN <>) appears on the execution status line. A double arrow indicates that scrolling is allowed both left and right. An example of the source display is shown in the following figure.

Important

Code Debug TSO automatically sets a before breakpoint (B) at the entry to the program and an after breakpoint (A) at the exit to the program.

Source Screen Showing TRIMAIN Program

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
                     BEFORE BREAKPOINT ENCOUNTERED
        ** END **



------   -------------------------------------------- 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).
000043        OPEN INPUT INFILE.
000044        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Setting Breakpoints

You can control program execution by using Code Debug TSO commands that set breakpoints. A breakpoint is a certain location in your program where you want program execution to stop.

A simple way to enter a breakpoint command is to type it in the line command area. Move the cursor to the compiler-generated statement number 43 at the OPEN verb, then type over the statement number with the B (Before) line command and press Enter. As shown in the following figure, a B appears in column 9 on statement 43, indicating that a before breakpoint has been set. This breakpoint causes program execution to pause before executing the OPEN statement.

Entering a Before Breakpoint at Statement 43

000041    INIT-PARA.
000042        MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4).
000043 B      OPEN INPUT INFILE.
000044        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Press PF12 or type GO to execute TRIMAIN until the breakpoint is reached. The program stops at statement 43, where the execution arrow is pointing and IN-REC is automatically kept in the Keep window. The execution status field on the fourth line also shows that execution is paused Before TRIMAIN:43, as shown in the following figure.

Program Stopped at Before Breakpoint on Statement 43

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                    BEFORE BREAKPOINT ENCOUNTERED
000012   01 IN-REC                          >                        NO ADDR
        ** END **

------   ----------------------------------------- Before TRIMAIN:43/AMODE 24 <>
000034 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).
=====> B      OPEN INPUT INFILE.
000044        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
000047           AT END

Press PF9 (GO 1) to execute the next statement.The program stops at statement 44 after the input file is opened and before the OUT-OF-RECS switch is set to N. Since the execution arrow is now paused on statement 44, IN-REC disappears from the Keep window and OUT-OF-RECS is automatically displayed.

Displaying File Information

Type the SHOW FILE command in the primary command line.The ddnames and DCB parameters that are specified in the JCL statements are listed, together with the file I/O status, as shown in the following figure.

File Attributes Displayed by the SHOW FILE Command

------------------------------- CODE DEBUG TSO - SHOW -------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM:  TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1995  COMP TIME:14:41:59
-------------------------------------------------- Before TRIMAIN:44/AMODE 24 ->
******************************* TOP OF DATA ************************************
*** FILE ATTRIBUTES FOR APPLICATION MODULE TRIMAIN  ***
                                                      DSORG RECFM BLKSI LRECL
NON-VSAM FILE FOR DDNAME INFILE       OPEN         DCB = PS   FB   27920    80
 DSN=SYS93271.T112126.RA000.FLGDAA1.R0000085      JFCB= PS   FB   27920    80
 DATA SET ALLOCATED ON VOLUME                     DSCB= PS   FB   27920    80
 ORGANIZATION = SEQUENTIAL         ACCESS MODE = SEQUENTIAL    RECFM = FB
 OPEN VERB OPTION = INPUT          LAST I/O STATEMENT = OPEN   STATUS = 00
*** END OF FILE ATTRIBUTE DISPLAY ***
******************************** BOTTOM OF DATA ********************************

Press PF3 (END) to return to the Source screen.

Displaying Data Values

Move the cursor to statement 42 where the table (N-CNTR) is initialized with zeros. Type over the statement number with the P (Peek) line command, and press Enter. The screen automatically scrolls to the DATA DIVISION statement where the table is defined, inserts a P in column 9, and displays the occurrence and value of N-CNTR, as shown in the following figure.

Displaying the Data Content of N-CNTR

------------------------------- CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN     MODULE: TRIMAIN   COMP DATE: 07/28/1995  COMP TIME:14:41:59
                                                -
000028   01 OUT-OF-RECS                       >  .
        ** END **

------   ----------------------------------------- Before TRIMAIN:44/AMODE 24 <>
000026            10  N-NAME          PIC X(21).
                                              1                         OCCURS
000027 P          10  N-CNTR          PIC 9 >  0000                     DECIMAL
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).
000033        05  SIDE-C              PIC 9(01).
000034 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.

Tab to the occurrence number and type over the 1 with a 2 and press Enter. Continue typing over the occurrence number, each time adding 1 to the previous number. Eventually, Code Debug TSO displays the warning shown in the following figure, indicating that the index boundary has been reached.

Message Indicating That the Index Boundary Has Been Reached

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
             OCCURRENCE NUMBER IS OUT OF RANGE FOR ITEM
                                                -
000028   01 OUT-OF-RECS                       >  .
        ** END **

------   ----------------------------------------- Before TRIMAIN:44/AMODE 24 <>
000026            10  N-NAME          PIC X(21).
                                              5                         OCCURS
000027 P          10  N-CNTR          PIC 9 >  ?????            INVALID DECIMAL
000028    01  OUT-OF-RECS             PIC X.
000029    01  TRIANGLE-TYPE           PIC 9.
000030    01  WORK-REC.
000031        05  SIDE-A              PIC 9(01).

Press PF6 (LOCATE *) to scroll to the current execution arrow. See the following figure.

TRIMAIN After Entering the LOCATE* Command

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN     MODULE: TRIMAIN   COMP DATE: 07/28/1995  COMP TIME:14:41:59
                                                -
000028   01 OUT-OF-RECS                       >  .
        ** END **

------   ----------------------------------------- Before TRIMAIN:44/AMODE 24 <>
=====>        MOVEN' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Enter an A line command on statement 46, setting an after breakpoint at the READ statement. Next, type the K2 line command on statement 46 to display the contents of working storage for WORK-REC (the second variable identified on line 46). Press Enter. The display is shown in the following figure. The K in column 9 of the window indicates that it is an explicitly kept item and distinguishes it from the automatically kept data.

Adding an Explicit Keep (WORK-REC) to the Keep Window

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
                            1 COMMANDS(S) COMPLETED
                                                 ---
000030 K 01  WORK-REC                          >  ...
                                                 -
000028   01  OUT-OF-RECS                       >  .
        ** END **
------   ----------------------------------------- Before TRIMAIN:44/AMODE 24 <>
=====>        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046 A      READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Press PF12 (GO) to execute TRIMAIN. As shown in the following figure, you can see that record 345 was read when the READ verb was executed. Note that the automatic keep of WORK-REC is only partially displayed since the window contains only 5 lines. To scroll the window, move the cursor into the window and use the PF7 and PF8 keys.

Displaying a Variable in a Keep Window

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                     NEXT LOGICAL INSTRUCTION IS TRIMAIN:49
                                                 ---
000030 K 01 WORK-REC                           >  345
                                                 ----+----1----+----2----+----3
SAME->   01 IN-REC                             >  345
                                                 ---
------   ------------------------------------------ After TRIMAIN:46/AMODE 24 <>
000044        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
====>> A      READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Press PF12 again. Paragraph ANALYZE-NEXT-REC is performed until EOF, and the next record, 789, is read in the second time through the loop. WORK-REC is updated to reflect the change. As you execute your program, Code Debug TSO updates the Keep window to reflect the current values of the explicitly kept data.

Debugging Subroutines

Statement 51 shows that the program TRIMAIN calls TRITST and passes parameters WORK-REC and TRIANGLE-TYPE. In order to examine how TRITST is processing these parameters, you can set a breakpoint at the beginning of TRITST to gain control of the execution. Type the following command on the primary command line:

   BEFORE TRITST:

The colon (:) after the program name indicates program qualification. Press PF12 (GO) to execute the program. Code Debug TSO sets a before module breakpoint at the beginning of the TRITST program and pauses execution at the PROCEDURE DIVISION USING statement in TRITST. Now, type the following command on the primary command line:

   PEEK LINKAGE

The Linkage Section (See the following figure) shows that the correct values, 789 for TST-REC and 0 for TYPE-OF-TRIANGLE, were passed from the driver TRIMAIN.

Displaying the Linkage Section in the Called Module TRITST

------   --------------------------------------------- Before TRITST/AMODE 24 <>
000009    LINKAGE SECTION.
                                          ---
000010 P  01  TST-REC.                  >  789
000011        05  A               PIC 9.
000012        05  B               PIC 9.
000013        05  C               PIC 9.
000014 P  01  TYPE-OF-TRIANGLE    PIC 9 >  0                            DECIMAL
=====> B  PROCEDURE DIVISION   USING  TST-REC
000016                            TYPE-OF-TRIANGLE.
000017    VALIDATE-TRIANGLE.
000018        ADD A B GIVING A-N-B.
000019        ADD A C GIVING A-N-C.
000020        ADD B C GIVING B-N-C.
000021        IF (B-N-C NOT > A) OR (A-N-C NOT > B) OR (A-N-B NOT > C)
000022           MOVE 4 TO TYPE-OF-TRIANGLE.

Analyzing Data Flow

To better understand how the parameters are processed in the subroutine, Code Debug TSO allows you to cross-reference data and to analyze the data flow in your program. The 01 level for TST-REC has three 05 levels: A, B, and C. Essentially, the elementary items are the aliases of a group item. Type the following command on the primary command line:

FIND TST-REC ALIAS ALL

Code Debug TSO highlights all the statements that reference (DEFINE, MODIFY, USE) TST-REC and its aliases. The message shown in the following figure is issued, which states how many data definitions were found.

Note

Enhanced FIND cannot be used in nested programs. Only a string FIND is valid.

Finding Statements That Reference TST-REC

------------------------------ CODE DEBUG TSO - SOURCE ------------------------
COMMAND ===>                                                     SCROLL===> CSR
           24 Data Refs:  4 DEFS, 20 USES found for TST-REC
                                                ---
000010   01 TST-REC                           >  789
000014   01 TYPE-OF-TRIANGLE                  >  0                       DECIMAL
        ** END **

------   --------------------------------------------- Before TRITST/AMODE 24 <>
000009    LINKAGE SECTION.
                                               ---
000010 P  01  TST-REC.                       >  789
000011         05  A                   PIC 9.                               DEF
000012         05  B                   PIC 9.                               DEF
000013         05  C                   PIC 9.                               DEF
000014 P  01   TYPE-OF-TRIANGLE        PIC 9 >  0                       DECIMAL
=====> B  PROCEDURE DIVISION   USING  TST-REC                               USE
000016                                TYPE-OF-TRIANGLE.
000017    VALIDATE-TRIANGLE.
000018        ADD A B GIVING A-N-B.                                       2 USE
000019        ADD A C GIVING A-N-C.                                       2 USE
000020        ADD B C GIVING B-N-C.                                       2 USE
000021        IF (B-N-C NOT > A) OR (A-N-C NOT > B)OR (A-N-B NOT > C)     3 USE
000022           MOVE 4 TO TYPE-OF-TRIANGLE.


The analysis concludes that parameter TST-REC is used, but never modified in the subroutine. What about parameter TYPE-OF-TRIANGLE? Type the following command on the primary command line:

   FIND TYPE-OF-TRIANGLE MOD ALL EXCLUDE

The EXCLUDE keyword was used to exclude lines that do not meet the search criteria. As shown in the following figure, the message 4 DATA MODS found for TYPE-OF-TRIANGLE is displayed in the message line. This indicates the parameter was modified four times.

Result of FIND TYPE-OF-TRIANGLE MOD EXCLUDE Command

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                  4 DATA MODS found for TYPE-OF-TRIANGLE
                                                ---
000010   01 TST-REC                           >  789
000014   01 TYPE-OF-TRIANGLE                  >  0                       DECIMAL
        ** END **
------   --------------------------------------------- Before TRITST/AMODE 24 <>
******************************** TOP OF MODULE *********************************
- - -    -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -   21 LINES NOT DISPLAYED
000022           MOVE 4 TO TYPE-OF-TRIANGLE.                               MOD
- - -    -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - 5 LINES NOT DISPLAYED
000028               MOVE 1 TO TYPE-OF-TRIANGLE                            MOD
- - -    -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - 2 LINES NOT DISPLAYED
000031                  MOVE 2 TO TYPE-OF-TRIANGLE                         MOD
- - -    -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  1 LINE NOT DISPLAYED
000033                  MOVE 3 TO TYPE-OF-TRIANGLE.                        MOD
- - -    -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  -  - 2 LINES NOT DISPLAYED
****************************** BOTTOM OF MODULE ********************************


The FIND command under Code Debug TSO is sensitive to COBOL-structure keywords as well as data reference keywords. For instance, you can use the FIND command to search conditional statements or I/O statements. The highlighting effect helps you capture the program logic and understand what the program does.

To reset all excluded lines in the program, enter END or press PF3.

Tracing Logic Flow

Subroutine TRITST evaluates the type of triangle by using TST-REC and then it updates TYPE-OF-TRIANGLE. Paragraph DETERMINE-TYPE (statement 23) has a nested IF structure. Code Debug TSO can automatically trace the logic flow to show which path was chosen. Type the following command in the primary command line to control the tracing speed:

   SET DELAY 1

Then type the following command on the primary command line and press Enter.

   GO TRACE

Tracing pauses when the after breakpoint in TRIMAIN is reached, as shown in the following figure.

Tracing is Paused for After Breakpoint in Calling Module TRIMAIN

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                     SCROLL===> CSR
                NEXT LOGICAL INSTRUCTION IS TRIMAIN:49
                                            ---
000030 K 01  WORK-REC                     >  563
                                            ----+----1----+----2----+----3
SAME->   01  IN-REC                          563
                                            ---
------   ------------------------------------------ After TRIMAIN:46/AMODE 24 <>
000044        MOVE 'N' TO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
====>> A      READ INFILE INTO WORK-REC
000047           AT END
000048           MOVE 'Y' TO OUT-OF-RECS.

Monitoring and Reviewing the Execution Path

Type the following command on the primary command line to activate review mode for all COBOL modules with a source listing member:

   MONITOR ALL

Press PF12 (GO) to start execution, followed by another PF12 to continue execution. When the after breakpoint is reached in TRIMAIN, type the following command on the primary command line to change the direction of execution processing:

   REVERSE

The execution status line shows that Code Debug TSO is reviewing in the reverse direction. See the following figure.

Review Mode Execution

------   ----------------------------------Reverse -
After TRIMAIN:46/AMODE 24 <>
 000044        MOVE 'N' TO OUT-OF-RECS.
 000045    ANALYZE-NEXT-REC.
 ====>> A      READ INFILE INTO WORK-REC
 000047           AT END

Now step through each statement backwards by pressing PF9 (GO 1) several times. Data values in the Keep window redisplay the original state as the MOVE, ADD, and READ verbs are being “undone.”

You can remove explicitly kept data from the Keep window by typing the following command in the primary command line:

   DELETE KEEP

If you want to remove a certain data item from the Keep window, type the D line command on the appropriate line. Press PF4 (EXIT) to exit the debugging session and to return to the Standard test screen.

 

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