Controlling program execution for COBOL
This section describes the Code Debug TSO commands that enable you to control program execution. Some of these commands, called breakpoint commands, are used to start and stop program execution at any time or when a specified condition occurs. Breakpoint commands let you designate the location of the pause by statement number, paragraph name, module name, or by the occurrence of a particular event. The other commands that control program execution are used to specify the program to be displayed as the active program.
When program execution is paused, you can enter other Code Debug TSO debugging commands to examine program data, analyze and follow program logic, and many other debugging functions. Execution resumes when you enter GO or press PF12.
Program execution is automatically stopped when an abend occurs. Code Debug TSO intercepts program abends and automatically pauses at the failing statement. Some abends can be corrected dynamically, and execution can be resumed without terminating the session.
Commands That Control Program Execution
The following are Code Debug TSO commands that control program execution.
AFTER
Stops program execution after the specified line of code is executed. An after breakpoint is automatically set on each GOBACK or STOP RUN statement in the driver program before the program begins executing.
AT
Sets a breakpoint at a sourceless main program or subprogram. Sourceless debugging and using the AT command are discussed in Debugging a Sourceless Program.
BEFORE
Stops program execution before the specified line of code is executed. A before breakpoint is automatically set on the PROCEDURE DIVISION statement in the driver program before the program starts executing. You must set a before breakpoint at the beginning of a called module if you want to stop execution before the called module executes.
COUNT
Counts the number of times an instruction or paragraph is executed and suspends program execution upon reaching a limit.
GO
Begins program execution and resumes execution after a pause.
INTERCEPT
Loads the specified module and sets a before breakpoint at the PROCEDURE DIVISION before the program begins executing and an after breakpoint on the GOBACK, STOP RUN, or EXIT PROGRAM.
ONETIME
Is functionally equivalent to a before breakpoint, stopping before a specified line of code is executed. However, the onetime breakpoint is removed automatically after it is encountered.
PAUSE
Pauses execution within a block of code that has been inserted.
PSEUDOSOURCE
Generates pseudo-assembler code for a program with no DDIO listing member. Using the PSEUDOSOURCE command is discussed in Creating Pseudo-Assembler Source.
RETEST
Reloads the program you are debugging and restarts the test session.
SKIP
Bypasses execution of source code, which can include bypassing a module. The SKIP command adds flexibility to your testing by letting you skip instructions that you do not want executed.
SOURCE
Loads the specified module and makes it the active program. Any subsequent Code Debug TSO commands that are entered are applied to the specified module.
TRACE
Traces the statements as it executes and suspends execution upon reaching a set limit, when attention has been requested, or when terminal IO has been done.
WHEN
Suspends execution when a data value changes or when a specified condition occurs.
Entering Program Control Commands
A simple way to enter a breakpoint command is to scroll to the source line where you want execution to pause, type the command in the line command area, and press Enter. You will see an indication of the breakpoint in column 9 on the Source screen.
To set a breakpoint at a specific location or occurrence of a specified event, enter the breakpoint command from the primary command line with a location operand or a condition for the stop. See the Command-and-syntax-reference for the valid location operands and parameters for a command.
If the primary command line is too small to list breakpoints or to stack commands, enter the SET CMDSIZE command to expand the command line up to three lines.
Setting Before and After Breakpoints
The following commands set before breakpoints on every paragraph and after breakpoints on statements 46 and 51:
When you press Enter, the screen looks like the following figure.
Result of Setting BEFORE ALL PARA and AFTER 4651 Breakpoints
COMMAND ===> SCROLL===> CSR
2 COMMAND(S) COMPLETED
** END **
------ -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000038 UNTIL OUT-OF-RECS = ’Y’.
000039 PERFORM ENDING-PARA.
000040 A GOBACK.
000041 B 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 B ANALYZE-NEXT-REC.
000046 A READ INFILE INTO WORK-REC
000047 AT END
000048 MOVE ’Y’ TO OUT-OF-RECS.
000049 IF OUT-OF-RECS = ’N’
000050 MOVE ZERO TO TRIANGLE-TYPE
000051 A CALL ’TRITST’ USING WORK-REC TRIANGLE-TYPE
The after breakpoint on statement 46 causes execution to pause after the READ statement is executed and before the next statement is executed—statement 48 or 49, depending on the AT END condition.The after breakpoint on statement 51 causes execution to pause after the called module TRITST returns to the calling module TRIMAIN.
To set a breakpoint in a module that is not currently displayed, you must qualify the breakpoint by entering the module name terminated with a colon (:) before the breakpoint name.
Alternatively, you can first display the source of the program (SOURCE command) that will be called later to establish module qualification, and then set breakpoints at the desired locations. See the Command-and-syntax-reference for information about qualification rules for Code Debug TSO commands.
If the program is a member of a statically-linked module that is not yet loaded in memory, bring the module into storage by entering the LOAD module-name command first, then the SOURCE program-name command.
The following demonstrates using a qualified before breakpoint on paragraph DETERMINE-TYPE in module TRITST, and using the SOURCE command to display the program TRITST to verify that the before breakpoint is set correctly.
When you press Enter, the screen displayed is similar to the following figure.
Result of Entering Qualified Breakpoint
COMMAND ===> SCROLL===> CSR
PROGRAM: TRITST MODULE: TRIMAIN COMP DATE: 07/28/1997 COMP TIME:14:41:59
** END **
------ -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000015 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.
000023 B DETERMINE-TYPE.
000024 IF TYPE-OF-TRIANGLE = 4
000025 NEXT SENTENCE
000026 ELSE
000027 IF (A = B) AND (B = C)
000028 MOVE 1 TO TYPE-OF-TRIANGLE
000029 ELSE
Enter SOURCE without a keyword or press PF6 (LOCATE *) to display the active program (TRIMAIN) where execution is currently paused.
Using the INTERCEPT Command
The INTERCEPT command loads the specified module and sets before and after module breakpoints. The command performs the function of the AFTER module breakpoint, BEFORE module breakpoint, and the SOURCE commands combined. The following demonstrates using the INTERCEPT command to access module TRIRPT.
When you press Enter, the screen displayed is similar to the following figure.
Result of the INTERCEPT Command
COMMAND ===> SCROLL ===> CSR
PROGRAM: TRIRPT MODULE: TRIMAIN COMP DATE: 07/28/1997 COMP TIME:14:41:59
** END **
------ -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000042 B PROCEDURE DIVISION USING TABLE-OF-NAMES-N-CNTRS.
000043 OPEN OUTPUT OUTFILE.
000044 WRITE OUT-REC FROM HDR-LINE.
000045 WRITE OUT-REC FROM BLANK-LINE.
000046 PERFORM MOVE-FIELDS.
000047 PERFORM WRITE-DTLS
000048 VARYING TX FROM 1 BY 1
000049 UNTIL TX > 4.
000050 WRITE OUT-REC FROM BLANK-LINE.
000051 ADD T-CNTR (1) T-CNTR (2) T-CNTR (3) T-CNTR (4)
000052 GIVING DTL-CNTR.
000053 MOVE ’INPUT RECORDS’ TO DTL-TITLE.
000054 WRITE OUT-REC FROM DTL-LINE.
000055 CLOSE OUTFILE.
000056 A GOBACK.
You can reset all the breakpoints you have entered since the beginning of your debugging session by issuing the RETEST command to obtain a “fresh” copy of the program. Or, you can resume execution of your program by issuing the GO command.
Resuming Execution With the GO Command
The GO command (PF12/PF24) is used to begin or resume execution of your program. Your program will execute until a breakpoint is encountered, an abend is intercepted by Code Debug TSO, or the end of the program is reached.
For example, in the program TRIMAIN, program execution paused when the before breakpoint was encountered on the PROCEDURE DIVISION. Suppose you entered the following command stream to set explicit after and before breakpoints:
The following figure shows the two after breakpoints set on statement 43 and 46. The at sign (@) on statement 46 indicates that the before breakpoint was also placed on the same line as the after breakpoint.
Both Before and After Breakpoints Set on Line 46
COMMAND ===> SCROLL ===> CSR
PROGRAM: TRIRPT MODULE: TRIMAIN COMP DATE: 07/28/1997 COMP TIME:14:41:59
------ ----------------------------------------------- Before TRIMAIN/AMODE 24
000042 MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4).
000043 A 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
When you press PF12 (GO), the execution arrow and active breakpoint field shown in the following figure indicate that the program is paused after statement 43, the first breakpoint reached during execution.
Result of Entering the GO Command
COMMAND ===> SCROLL===> CSR
NEXT LOGICAL INSTRUCTION IS TRIMAIN:44
----+----1----+----2----+----3
SAME-> 01 IN-REC > ..............................
** END **
------ ------------------------------------------ After 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).
====>> A 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.
At this point, you could do any of the following:
- Set additional breakpoints
- Insert Code Debug TSO commands into the program
- Enter GO to resume execution
- Enter GO 1 to step through the execution line-by-line
- Enter EXIT to exit from the debugging session.
For this example, enter the RETEST command to obtain a “fresh” copy of the program.
Setting Conditional Breakpoints
The GO n, COUNT, WHEN, PAUSE, and TRACE commands are used to set breakpoints when a specified condition occurs.
Using the GO n Command
Using the GO command without any arguments resumes execution until the next breakpoint is reached, Code Debug TSO intercepts a program abend, or the program completes execution. The GO command can also conditionally execute a specified number of statements, paragraphs, or programs if an integer argument is entered with the command. It can also trace each one if the TRACE parameter is entered with the command. For example, entering
executes five statements before pausing. Entering
executes five statements and traces each one, and entering
executes five paragraphs before pausing.
You can single-step through the code to understand the effect of executing each statement by using the GO 1 command or pressing PF9. The GO 1 command stops at paragraph and section names, as well as at statements that contain the IF construct or any executable verbs. For this example, stop at statement 51.
When a GO 1 command is issued from any statement that transfers control to another module (for example, CALL, GOBACK, EXIT PROGRAM), execution pauses when control returns to the current module, unless a breakpoint is encountered within the called module.
The following figure. shows the result of entering the GO 1 command when execution was paused at the CALL to TRITST at statement 51 and no breakpoints are set in TRITST.
Single Stepping Through Code Within the Current Module
COMMAND ===> SCROLL===> CSR
PROGRAM: TRIMAIN MODULE: TRIMAIN COMP DATE: 07/28/1997 COMP TIME:14:41:59
COBOL TX > 1 INDEX
000029 01 TRIANGLE-TYPE > 4 DECIMAL
** END **
------ ----------------------------------------- Before TRIMAIN:52/AMODE 24 <>
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.
000049 IF OUT-OF-RECS = ’N’
000050 MOVE ZERO TO TRIANGLE-TYPE
=====> CALL ’TRITST’ USING WORK-REC TRIANGLE-TYPE
000052 SET TX TO TRIANGLE-TYPE
000053 ADD 1 TO N-CNTR(TX)
The following figure demonstrates the result when execution was paused at the CALL to TRITST at statement 51, with a before module breakpoint set at the beginning of TRITST. Then, when you press PF9 or enter GO 1, execution starts in the TRITST module because a BEFORE TRITST: breakpoint was set.
Stepping into a Called Module Using the GO 1 Command
COMMAND ===> SCROLL===> CSR
BEFORE BREAKPOINT ENCOUNTERED
---
000010 01 TST-REC > 345
000014 01 TRIANGLE-TYPE > 0 DECIMAL
** END **
------ --------------------------------------------- Before TRITST/AMODE 24 <>
=====> 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.
000023 DETERMINE-TYPE.
000024 IF TYPE-OF-TRIANGLE = 4
000025 NEXT SENTENCE
000026 ELSE
000027 IF (A = B) AND (B = C)
000028 MOVE 1 TO TYPE-OF-TRIANGLE
000029 ELSE
To bring a new copy of your source into the display, enter RETEST.
Using the COUNT MAX Command
The COUNT command is used to monitor execution coverage by maintaining statement execution counts. When the MAX keyword is used with the COUNT command, a conditional breakpoint with a count limit is set. When the limit is reached, program execution pauses and the message SPECIFIED EXECUTION MAX HAS BEEN REACHED is displayed. When the COUNT command is issued, a 7-digit counter appears in columns 74 through 80.
=====> ANALYZE-NEXT-REC. 0000003
The counter field can be typed over to set or remove the limit. For example, you can type over the counter with a higher limit and press Enter to raise the preset maximum limit, or you can zero out the counter and press Enter to remove the limit.
Using the WHEN Command
The WHEN command lets you stop execution when a program variable changes value or when a specified event takes place. Code Debug TSO checks the condition after every statement in the current module and pauses if the condition is met. The WHEN command can be used with the following arguments:
Variable-name
Suspends execution when a statement altering the value of the variable is executed. The variable content can be monitored by opening a Keep window and displaying the variable content.
Condition
Suspends execution when the specified condition is met. You can enter a relational condition using expressions such as the following:
WHEN TOTAL-SUM > 50000
WHEN WS-TRAN-KEY = HIGH-VALUES
WHEN OUT-OF-RECS CHANGES
For example, enter the following WHEN command to conditionally pause when the index TX is changed, and enter the KEEP command on index TX to monitor the change:
The following figure shows the result of resuming execution by pressing PF12 (GO). Note that the automatic keep function also keeps the value of TX and TRIANGLE-TYPE. However, these values will disappear as the current line changes, but the KEEP command will continuously monitor the value of TX. The DELETE WHEN command can be used to remove the when condition.
Reaching the When Breakpoint
COMMAND ===> SCROLL===> CSR
WHEN TX CHANGES
COBOL K TX > 3 INDEX
COBOL TX > 3 INDEX
000029 01 TRIANGLE-TYPE > 3 DECIMAL
** END **
------ ------------------------------------------ After TRIMAIN:52/AMODE 24 <>
000051 CALL ’TRITST’ USING WORK-REC TRIANGLE-TYPE
====>> SET TX TO TRIANGLE-TYPE
000053 ADD 1 TO N-CNTR(TX)
000054 ENDING-PARA.
000055 CLOSE INFILE.
000056 CALL ’TRIRPT’ USING NAME-N-CNTR-TABLE.
Using the Inserted PAUSE Command
The PAUSE command can be dynamically inserted in the COBOL source code to set a breakpoint following the execution of a statement. You can specify a condition in which the pause breakpoint is to occur, by also inserting the IF...ELSE construct associated with it.
The PAUSE command must be used in conjunction with the INSERT command. For information on the usage convention of the INSERT command and the effect of inserting a PAUSE command, see to Inserting Statements.
Using the TRACE Command
The TRACE command is used to monitor the execution of specified statements or paragraphs in your program. The specified statements or paragraph names are highlighted as they are executed until a breakpoint is reached, an abend is intercepted by Code Debug TSO, a terminal I/O is issued, or a keyboard interrupt is detected.
When the TRACE command is used with the MAX keyword, the tracing function pauses when the number of executions reaches the preset limit. The default maximum limit is 25.
For example, if you enter the following command for a program that does not have any breakpoints set and press PF12 (GO) to resume execution:
the program will pause following the execution of 25 statements and display the message 25 TRACE BREAKPOINTS HAVE BEEN EXECUTED.
In order to override the default maximum limit, you must enter the MAX keyword with an integer other than 25 as an argument with the TRACE command.
The tracing speed can be controlled by using the SET DELAY command prior to entering the TRACE command. For instance, entering the following command will slow down the execution speed to one second:
You can interrupt tracing and suspend execution by using the Attention key. While tracing is in progress, the keyboard is unlocked and, depending upon your terminal type and network configuration, you may be able to use other keys to stop tracing. To end a TRACE command, use DELETE TRACE.