User interface to Code Debug TSO for COBOL
This section describes how to interact with Code Debug TSO in general. The screen formats, PF key assignments, command processing, and attention key processing are discussed.
Code Debug Screens
Code Debug uses screens that are like ISPF/PDF, making the Code Debug menus and utility screens self-explanatory. The Source, Log, Show, and Memory screens have a similar format. The following figure displays a COBOL program in the Code Debug Source screen, and COBOL Program Encountering an Abenddisplays a COBOL program on the same screen encountering an abend.
COBOL Program in the Source Screen
COMMAND ===> SCROLL===> CSR
PROGRAM: TRIMAIN MODULE: TRIMAIN COMP DATE: 08/23/1995 COMP TIME:14.41.59
** 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.
The screen areas are described as:
Title
(line 1): Identifies the screen name: Source, Log, Show, Memory, and so forth. If the program has been optimized, an indicator is displayed in the upper right corner based on the release of the COBOL compiler and level of code and storage optimization used to compile the source code, for example OPT, OPT(0), OPT(1,N), OPT(1,Y), OPT(2,N), or OPT(2,Y).
Command area
(line 2): Primary command line, which can be increased to three lines using the SET CMDSIZE command.
Scroll amount
(line 2): Indicates the current scroll amount. You can type over the current value with one of the following values:
1 to 9999 | Scrolls by the number of lines or columns. |
CSR or C | Scrolls based on the current position of the cursor. |
DATA or D | Scrolls by one line or column less than PAGE. |
HALF or H | Scrolls by a half page. |
PAGE or P | Scrolls by one page. |
Program
(line 3): Identifies the source program currently displayed. This is an unprotected field and can be typed over with another program name.
Module
(line 3): Displays the load module name.
Compile date
(line 3): Displays the compile date.
Compile time
(line 3): Displays the compile time.
COBOL Program Encountering an Abend
COMMAND ===> SCROLL ===> CSR
S0C7 ABEND ENCOUNTERED, USE "AA SNAP" COMMAND FOR ADDITIONAL INFORMATION
000011 05 A > ?? INVALID DECIMAL
000012 05 B > ?? INVALID DECIMAL
000006 01 A-N-B > ???? INVALID DECIMAL
** END **
------ -------------------------------- S0C7 Abend at TRITST:18/AMODE 31 <>
000015 PROCEDURE DIVISION USING TST-REC
000016 TYPE-OF-TRIANGLE.
000017 VALIDATE-TRIANGLE.
=====> 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
Message area
(COBOL Program Encountering an Abend, line 3): Displays short or informational messages. When a message is issued, it overlays the program information in line 3. Press Enter to flush the message and display the program information. Additional information can be accessed by pressing PF1 (HELP).
Keep Window
(lines 4-8): Automatically displays data referenced in the current statement; i.e., the statement where the execution arrow is located when the breakpoint takes effect. Explicitly kept data is also displayed. Explicitly kept items are denoted by a K in column 9 of the window.
The data in the window can be scrolled by moving the cursor to the Keep window and using the PF7 (UP) and PF8 (DOWN) keys to scroll vertically and the PF22 (DRIGHT) and PF23 (DLEFT) keys to scroll horizontally. You can also control the size of the window and, for automatic keeps, the placement of the automatically kept items. See the SET command in Displaying Test Session Settings for additional information.
The SET AUTOKEEP ON/OFF command toggles the effect of the Automatic Keep function.
Execution status
(line 9): Identifies the current execution point in your program. The <> shown at the end of this line indicates that the source can be scrolled to the left and/or right.
The execution status line may also display one or more of the following:
- Whether execution is halted before or after the specified line
- Program name
- Abend code (COBOL Program Encountering an Abend)
- 24, 31, or 64 bit addressing mode.
Source area
As shown in both Figure 2-1 and Figure 2-2, the source area begins on line 10 and displays 68 to 70 bytes of the source code on the screen at a time. The source can be scrolled vertically using the PF7 (UP) and PF8 (DOWN) keys and horizontally using the PF10 (RIGHT) and PF11 (LEFT) keys. When an Automatic Keep window is visible, the data in the window can also be scrolled vertically using the PF7 and PF8 keys and horizontally using the PF22 and PF23 keys.
The After, Before, Onetime, Peek, and Skip indicators are displayed on the left side of the source in column 9. A 7-digit counter set by the COUNT command is displayed on the right side beginning at column 74.
PF Keys
The default settings for the 24 Code Debug PF keys are listed in the following table. These values are valid during the Code Debug TSO session. ISPF PF keys are not affected. The ISPF KEYS command or the SET PFn command can be used to override the defaults.
Default Program Function (PF) Keys
PF Key | Default Setting | Description of Function |
---|---|---|
PF1/PF13 | HELP | Elaborates an Code Debug TSO message and invokes the context-sensitive tutorial facility. |
PF2 | PEEK CSR | Displays the contents of the data name defined by the current cursor position. The cursor must be in the Source window under a valid data name. |
PF14 | FIND CSR | Finds the character string located under the cursor position. |
PF3/PF15 | END | Returns you to the previous menu if you are in the Log, Help, Browse, or Show functions. |
PF4/PF16 | EXIT | Ends the current Code Debug TSO session. |
PF5 | FIND | Repeats the action of the previous FIND command. |
PF17 | FIND IND | Scrolls the source display to successive levels of indirect references related to a previously entered FIND INDIRECT command. |
PF6/PF18 | LOCATE * | Scrolls the source display to the current location where execution was suspended. |
PF7/PF19 | UP | Scrolls the source or data in the Keep window up, or toward the top of the file. |
PF8/PF20 | DOWN | Scrolls the source or data in the Keep window down, or toward the bottom of the file. |
PF9/PF21 | GO 1 | Executes the next logical instruction in your program, then pauses. |
PF10 | LEFT | Scrolls the source display to the left. |
PF11 | RIGHT | Scrolls the source display to the right. |
PF12/PF24 | GO | Starts or resumes execution of your program. |
PF22 | DLEFT | Scrolls data in an Automatic Keep, Keep, or Peek window to the left. |
PF23 | DRIGHT | Scrolls data in an Automatic Keep, Keep, or Peek window to the right. |
Command Processing
In interactive mode, the results of command execution are immediately visible on the source display.
Code Debug TSO commands can be entered in three ways:
- Type the command in the primary command area and press Enter. Command stacking, delimited by a semicolon (;), is allowed. The primary command area can be extended up to three lines by using the SET CMDSIZE command. The previous primary command can be recalled by entering a question mark (?).
- Press the PF key that was assigned to the desired command. See above table for a list of the PF key assignments.
- Type over the 6-digit compiler-generated statement number with a valid line command and press Enter. Code Debug TSO records the line command in the session log in the same manner as the primary command.
Lowercase Conversion
By default, commands entered in lowercase are converted to uppercase. To override the default, use the SET CAPS OFF command. Also, to display lowercase data, use the SET LOWCASE ASIS command.
Attention Key Processing
When you press the attention key while Code Debug or your application is executing, the message
is displayed. If you enter HELP, a screen containing information similar to Figure 2-3 is displayed. Enter the option you want to perform.
Attention Key Processing Options
PAUSE TO DYNAMICALLY INVOKE THE PAUSE COMMAND
EXIT TO TERMINATE THE TEST SESSION
LOG TO DISPLAY THE LOG PRIOR TO TERMINATION
PSW TO DISPLAY THE CURRENT PSW ADDRESS
GPREGS TO DISPLAY THE CURRENT GENERAL PURPOSE REGISTERS
STORAGE <address> TO DISPLAY STORAGE AT THE SPECIFIED ADDRESS
WHERE TO DISPLAY THE CURRENT MODULE AND OFFSET
WHERE <address> TO DISPLAY THE MODULE AND OFFSET OF <address>
WHERE <module> TO DISPLAY THE ADDRESS OF THE SPECIFIED MODULE
GO TO RESUME TEST EXECUTION (or PRESS ENTER)
If pressing the Attention key interrupts an IMS Fast Path test and you then enter the EXIT command, Code Debug IMS will detach your IMS region and an S33E system abend will be reported as you return to the starting test panel. Message XPD1202 records the abend in the Code Debug session log.
When you press the attention key while Code Debug is waiting for input (e.g., stopped at a breakpoint), the message
is displayed. If you press the attention key again, the message
is displayed. Pressing attention again will take you to the READY prompt.