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.

Modifying program logic for COBOL


This section describes the Code Debug TSO commands that let you modify program logic by bypassing code segments, adding statements, and forcing logic changes. The SKIP, INSERT, GOTO, and MOVE commands allow you to try out fixes dynamically without requiring any source code modification.

Bypassing Code With the SKIP Command

Warning

Be careful using the SKIP command. When you SKIP a single source statement, you can also be inadvertently bypassing execution of several underlying machine instructions. This can affect subsequent statements and cause unpredictable results including, but not limited to, abends (especially S0C4 and S0C7), loops, storage overlays, and logic and display errors.

Unwanted code can be bypassed using the SKIP command. There is no need to comment out the code and recompile the program for it to take effect. For example, a call to a submodule that is not yet written can be bypassed without requiring a program stub to be developed. Following figure shows the effect of skipping module TRITST and pausing execution following the CALL statement. The following commands were issued:

   SKIP TRITST:AFTER 51GO

The effect of the SKIP command can be seen in the parameters WORK-REC and TRIANGLE-TYPE as they are displayed automatically in the Keep window. You could also issue KEEP commands for TRIANGLE-TYPE and WORK-REC to continuously display these parameters.

Result of Entering the SKIP TRITST: Command

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                  NEXT LOGICAL INSTRUCTION IS TRIMAIN:52
000029   01 TRIANGLE-TYPE                   >  0                        DECIMAL
                                              ---
000030   01 WORK-REC                        >  345
        ** END **

------   ------------------------------------------ After TRIMAIN:51/AMODE 24 <>
000050           MOVE ZERO TO TRIANGLE-TYPE
====>> A         CALLTRITSTUSING WORK-REC TRIANGLE-TYPE
000052           SET TX TO TRIANGLE-TYPE
000053           ADD 1 TO N-CNTR(TX)
000054    ENDING-PARA.
000055        CLOSE INFILE.
000056        CALLTRIRPTUSING NAME-N-CNTR-TABLE.
****************************** BOTTOM OF MODULE ********************************

The parameter TRIANGLE-TYPE is left untouched since the CALL to TRITST was bypassed. You can avoid a S0C7 abend by moving a valid value to TRIANGLE-TYPE.

The SKIP command can be used with a statement, a range of statements, a paragraph name, or a module name.

There are a couple of situations to be aware of when using the SKIP command. In order to bypass an entire IF statement, you must skip each verb, not just the statement containing the IF condition. Also, if you skip a statement that sets a switch or flag, the execution path could change or end in an infinite loop. More subtly, the COBOL compiler generates multiple instructions for each COBOL verb. Some of these instructions can load base pointers and base registers for statements. Since a SKIP bypasses all instructions associated with the verb, a S0C1 or S0C4 can result. The SKIP command should be deleted in this case. Use the DELETE SKIP command or the DS line command to delete the skip.

The SKIP command can be combined with inserted statements to test alternative logic flow. The following figure shows that the original IF statement starting with statement 40 was skipped and completely replaced by the inserted IF logic above it. The insert lines (’’’’’’) were opened up by issuing an I (Insert) line command (I 3) on line 39. See following Inserting Statements for more information on inserting statements.

Inserted Statements Must Precede the COBOL Statements That Are Skipped

000039         ADD +1 TO COUNTER
’’’’’’         if record-type =1and out-of-recs =N
’’’’’’           move spaces to hold-area
’’’’’’         end-if
000040 S       IF RECORD-TYPE =1
000041 S         MOVE SPACES TO HOLD-AREA.
000042         MOVE SPACES TO RECORD-TYPE

This approach makes it easy to experiment with several potential fixes.

Inserting Statements

You can insert Code Debug TSO commands, such as MOVE, PEEK, GOTO, and PAUSE, using the IF...ELSE... constructs to your program. The capability to insert statements allows you to test fixes before you update the source code and actually recompile the program. Inserted statements are executed after the last logical statement as if they are part of the source code. Only one inserted command per line is permitted.

You can also dynamically insert SQL statements and prototype Db2 applications if you have Code Debug Db2 and File-AID for Db2 installed. See Using-Code-Debug-Db2-Extension for more information.

The following figure shows the effect of the inserted statements being executed. The PAUSE command can be used to set a breakpoint within a block of inserted Code Debug TSO commands or SQL statements. When the pause breakpoint is encountered, Code Debug TSO temporarily pauses execution, issues a message, and returns control to you, as shown.

Result of Executing Inserted Statements and Taking PAUSE

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                     SCROLL===> CSR
                    PAUSE REQUESTED BY INSERTED COMMAND
                                                 ---
000030   01 WORK-REC                           >  111
        ** END **

------   ----------------------------------------- Before TRIMAIN:46/AMODE 24 <>
000040         GOBACK.
000041 A  INIT-PARA.
000042        MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4).
000043        OPEN INPUT INFILE.
000044        MOVENTO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
’’’’’’           IF WORK-REC =345
’’’’’’              KEEP WORK-REC
’’’’’’              MOVE111TO WORK-REC
=====>              PAUSE
’’’’’’           END-IF
000047           AT END

The Source display screen is designed after the ISPF/PDF editor. The COBOL source code itself cannot be edited; however, you can insert Code Debug TSO commands to the display-only source code by typing over the statement number area with the I (Insert) line command. Use the D (Delete) line command to delete any lines. The syntax of the inserted statements is checked by Code Debug TSO before they are executed. If the syntax is incorrect, an error message is generated and the incorrect statement is highlighted when you press Enter, as illustrated in the following figure.

Syntax Checking for Inserted Statements

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                    IF/ELSE/ENDIF LOGIC UNBALANCED
        ** END **



------   -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000045    ANALYZE-NEXT-REC.
000046        READ INFILE INTO WORK-REC
’’’’’’           IF WORK-REC =345
’’’’’’              KEEP WORK-REC
’’’’’’              MOVE111TO WORK-REC
’’’’’’              PAUSE
000047           AT END
000048           MOVEYTO OUT-OF-RECS.

INSERT Processing

You can enter the I (Insert) line command on a COBOL statement containing an executable verb (PMAP record) and enter Code Debug TSO commands following the statement. Only one inserted command per line is permitted. You cannot insert lines after a statement containing only ELSE, AT END, or scope terminators (END-IF, END-READ, END-PERFORM), where a breakpoint cannot be set. The reason for this rule is that Code Debug TSO internally generates an after breakpoint on the COBOL statement where the I line command is entered and interpretively executes the inserted statements only if the internal after breakpoint is reached. In other words, the inserted statements are associated with the COBOL code above them.

When commands are embedded at the end of a conditional structure that is delimited by a period or a scope terminator, the inserted statements will be executed when the COBOL code above them is reached. If you want the inserted statements to be executed only when the true path is taken, place the insert anywhere inside the true path, as shown in the following figure. If you want the inserted statements to be executed only when the false path is taken, place the insert anywhere inside the false path.

Inserting Statements Following a Conditional Construct

000044        MOVENTO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC.
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).
’’’’’’           KEEP OUT-OF-RECS
=====>           PAUSE
000054    ENDING-PARA.

Placing the I line command on branching verbs such as PERFORM, GOBACK, and EXIT is not permitted. A message INSERT NOT PERMITTED FOLLOWING verb is issued when you attempt to do so. If you wish to execute statements following the return from the actual performed paragraph, insert the statement after the last executable code in the out-of-line paragraph.

See the INSERT command in the Command-and-syntax-reference for a list of commands that can and cannot be inserted in your program.

Redirecting Logic

You can dynamically alter the control flow and force the program to take a certain path by using the GOTO command, or by simply changing the data that is processed using the MOVE command and let the program take its own course.

Using the GOTO Command

Warning

Be careful using the GOTO command. When you GOTO a source statement, you can also be inadvertently bypassing execution of several underlying machine instructions. This can affect subsequent statements and cause unpredictable results including, but not limited to, abends (especially S0C4 and S0C7), loops, storage overlays, and logic and display errors.

The GOTO command forces logic changes by redirecting the next executable statement to elsewhere in the program. The command can be used to execute a wild branch, to bypass statements, to test a loop repeatedly, or to take an alternate path. If your module contains nested programs, you cannot use GOTO to branch to another nested program or to go to a separately compiled program. GOTO is restricted to the current program.

Enter the following GOTO command to redirect execution from statement 58 to statement 50 in the middle of a PERFORM VARYING clause, so that this statement never gets completed.

GOTO 50

The following figure shows the result of entering this command.

Result of Entering the GOTO Command

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                    SCROLL ===> CSR
                       EXECUTION RESUMES HERE
                                              ----+----1----+----2----+----3
MORE-> K 01 DTL-LINE                        >  NUMBER OF ISOSCELES TRIANGLES
COBOL  K    TX                              >  3                          INDEX
000012   01 OUT-REC                         >                           NO ADDR
------   ------------------------------------------ Before TRIRPT:50/AMODE 24 <>
000047        PERFORM WRITE-DTLS
000048                VARYING TX FROM 1 BY 1
000049                UNTIL TX > 4.
=====>        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        MOVEINPUT RECORDSTO DTL-TITLE.
000054        WRITE OUT-REC FROM DTL-LINE.
000055        CLOSE OUTFILE.
000056        GOBACK.
000057    WRITE-DTLS.
000058        MOVE T-NAME (TX) TO DTL-TITLE.
000059        MOVE T-CNTR (TX) TO DTL-CNTR.
000060        WRITE OUT-REC FROM DTL-LINE.
000061    MOVE-FIELDS

Using the MOVE Command

The MOVE command, on the other hand, indirectly allows you to change the execution flow by modifying the values of switches, flags, and data that control the path to be taken. The following figure shows an example of altering TST-REC so that the EVALUATE statement will set the EQUILATERAL switch instead of the SCALENE switch.

Altering Path by Modifying Data

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===> MOVE 555 TO TST-REC                                SCROLL ===> CSR
PROGRAM: TRITST2    MODULE: TRITST2   COMP DATE: 07/28/1995  COMP TIME: 11:59:17
                                                    ---
000011 K 01 TST-REC                               >  563
000012   05 A                                     >  5                  DECIMAL
000013   05 B                                     >  6                  DECIMAL
000014   05 C                                     >  3                  DECIMAL
------   ----------------------------------------- Before TRITST2:31/AMODE 24 <>
=====> B             EVALUATE A = B ALSO B = C ALSO A = C
000032                   WHEN TRUE ALSO TRUE ALSO TRUE
000033                        SET EQUILATERAL TO TRUE
000034                   WHEN TRUE ALSO ANY  ALSO ANY
000035                        SET ISOSCELES TO TRUE
000036                   WHEN ANY  ALSO TRUE ALSO ANY
000037                        SET ISOSCELES TO TRUE
000038                   WHEN ANY  ALSO ANY  ALSO TRUE
000039                        SET ISOSCELES TO TRUE
000040                   WHEN OTHER
000041                        SET SCALENE TO TRUE
000042               END-EVALUATE
000044 A      GOBACK.
******************************* BOTTOM OF MODULE *******************************


 

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