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.

Inspecting program data for COBOL


Code Debug TSO lets you view the contents of variables defined in your program and the data that is passed to the working storage and the linkage. The data is formatted by the data type defined in your program.

Described in this section are the Automatic Keep function and the Code Debug TSO commands KEEP, PEEK, MOVE, MEMORY, and GPREGS.

When you have Code Debug Db2 Extension and File-AID for Db2 installed, you can also browse and edit Db2 table data during a Code Debug TSO session. See Using-Code-Debug-Db2-Extension for more information.

Displaying and Modifying Program Variables

Code Debug TSO automatically displays the values of data items referenced by the current execution statement whenever execution halts. These values are displayed in a Keep window at the top of the source display as shown in the following figure. Each time the program halts, a new set of variables and their values are displayed.

Keep Window Displaying Automatic Keeps

-------------------------- CODE DEBUG TSO - SOURCE -------------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN    COMP DATE: 07/28/1996  COMP TIME:12:15:45
                                              ----+----1----+----2----+----3
SAME->   01 IN-REC                          >  345
                                              ---
000030   01 WORK-REC                        >  345
        ** END **
------   ----------------------------------------- Before TRIMAIN:46/AMODE 24 <>
000042        MOVE ZERO TO N-CNTR (1) N-CNTR (2) N-CNTR (3) N-CNTR (4).
000043        OPEN INPUT INFILR.
000044        MOVENTO OUT-OF-RECS.
000045    ANALYZE-NEXT-REC
=====> B      READ INFILE INTO WORK-REC
000047           AT END
000048           MOVEYTO OUT-OF-RECS

If a variable of interest is not automatically kept, you can use an explicit KEEP command or the PEEK command to temporarily display the contents of the variable.

The KEEP command is used when you want to continuously display the contents of a variable. When the KEEP command is entered, Code Debug TSO continuously displays and updates the data values in the Keep window until you delete the keep. Code Debug inserts a K in column 9 of the Keep window to differentiate between the explicitly kept items and the automatically kept items.

Important

You have the option of creating a separate window called the Automatic Keep window located at the bottom of the source display to hold the automatically kept items. To do this, use the SET AUTOKEEP n command. See the SET command in the Command-and-syntax-reference for additional information.

The PEEK command is used when you want to temporarily display the contents of a variable. When the PEEK command is entered, Code Debug TSO scrolls to the DATA DIVISION statement, displays the data values in a window on the right side of the screen, and inserts a P in column 9 of the source. Some of the statement will be overlaid. When you resume execution, the window is removed from the screen. Examples of the Keep and Peek windows are shown in the following figure.

Important

Use the LOCATE * command (PF6), to return to the location where execution is paused.

Use the DELETE command to remove a Keep or Peek display.

Use the SET AUTOKEEP OFF command to turn off the Automatic Keep function.

Keep and Peek Windows

-------------------------- CODE DEBUG TSO - SOURCE -------------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN     MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME:12:15:45
                                              ---
000030 K 01 WORK-REC                        >  345



------   --------------------------------------------- After TRIMAIN/AMODE 24 <>
000028    01  OUT-OF-RECS              PIC X.
000029    01  TRIANGLE-TYPE            PIC 9.
                                              ---
000030 P  01  WORK-REC.                     >  345
000031        05  SIDE-A               PIC 9(01).

Automatic Keep, Keep, and Peek windows display data in the same format: the statement number where the variable is declared, the level number, the data name, the current value, and the data type.

The level number appears only if the variable is declared in the source as a structure with level numbers. Data values are displayed according to scaling and precision attributes. Alphabetic items are displayed as characters, and numeric items are displayed as DECIMAL, PACKED decimal (COMP-3), HALFWORD (COMP), FULLWORD (COMP), INDEX, or FLOAT (COMP-1, COMP-2), depending on the internal representation. Tables are shown by rows and columns, rather than in a linear fashion.

The Keep window is both scrollable and adjustable in size. The window becomes scrollable when the data exceeds the size of the window. Scrolling is cursor sensitive; that is, the cursor must be in the Keep window for vertical scrolling to take place. Move the cursor to the window and use the PF7 (UP) and PF8 (DOWN) keys to scroll the data vertically. Use the PF22 (DRIGHT) and PF23 (DLEFT) keys to scroll the Keep and Peek windows horizontally. To ensure that the cursor remains in the Keep window while scrolling, put the cursor on the segmented execution status line before using your scroll keys. You can do this either with the up and down arrow keys or with the Tab key.

You can set the size of the Source, the Keep window, and the Automatic Keep window. The automatically kept items can, by default, be displayed in the Keep window at the top of the screen or in a separate Automatic Keep window at the bottom of the screen. See the SET command in the Command-and-syntax-reference for additional information.

The contents of variables displayed in a window can be changed by using the MOVE command or by typing over them (implicit MOVE).

If the OCCURS field is not associated with an index or subscript, it can also be typed over to display a different table entry. An occurrence modifier can also be appended to increment or decrement through the table entries. Erasing the occurrence indicator (S= or I=) will disassociate that position with its underlying variable. See the KEEP command Usage Notes section in the Command-and-syntax-reference for more information about keeping tables and/or arrays and using the OCCURS field.

Using the KEEP Command

The KEEP command lets you continuously view the contents of program variables in a window opened at the top of the source display. You can enter the KEEP primary command with the name of the variable or you can enter the K line command either in the Procedure Division (where the variable is referenced) or in the Data Division (where the variable is defined). If the data exceeds 30 bytes, the field becomes scrollable, and it is indicated by the MORE-> sign in the statement number area.Tables are formatted by each dimension when the KEEP command is entered at the elementary level. If the OCCURS field is not associated with an index or subscript, it can be typed over to browse through the table by each entry. Also, a relative subscript can be appended to increment or decrement the occurrences. If the data displayed is a character data type, a column template is displayed to show the length. The length of a numeric item, however, is a function of the internal format.The alphabetic items are displayed as characters and the numeric items are displayed as DECIMAL, PACKED decimal (COMP-3), HALFWORD (COMP), FULLWORD (COMP), INDEX, or FLOAT (COMP-1, COMP-2), depending on the internal representation. Tables will be shown by row and column, rather than in a linear fashion.

The KEEP command has the following format:

KEEP (K line command)

Keeps the value of a variable.

KEEPE (KE line command)

Keeps the values of the elementary items that are part of a group item.

KEEPH (KH line command)

Keeps the hexadecimal values of a variable.

Use the DELETE command (DELETE KEEP or D line command) to remove the display resulting from the KEEP commands.

Examples for using the KEEP command are given as follows. Note that an AFTER 53 breakpoint was entered in the TRIMAIN program before execution was resumed.

The following figure shows the result of entering the KEEP command for the variables WORK-REC and N-N-C. For this example, the automatic Keep window was moved to the bottom of the display with the SET AUTOKEEP 5 command so that all of the explicitly kept items will show in the Keep window without scrolling.

Result of Entering the KEEP Command for WORK-REC and N-N-C

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                NEXT LOGICAL INSTRUCTION IS TRIMAIN:45
                                              1                          OCCURS
                                              ----+----1----+----2----+
000024 K 05 N-N-C                           >  EQUILATERAL TRIANGLES0000
                                              ---
000030 K 01 WORK-REC                        >  345
------   ------------------------------------------ After TRIMAIN:53/AMODE 24 <>
000052           SET TX TO TRIANGLE-TYPE
====>> A         ADD 1 TO N-CNTR(TX)
000054    ENDING-PARA.
000055        CLOSE INFILE.
000056        CALLTRIRPTUSING NAME-N-CNTR-TABLE.
****************************** BOTTOM OF MODULE ********************************


------   -----------------------------------------------------------------------
                                             I=4                        OCCURS
000027   10 N-CNTR                         >  0001                      DECIMAL
COBOL       TX                             >  4                           INDEX
        ** END **

When a table element is displayed, Code Debug TSO inserts an OCCURS field. Above data shows data name N-N-C in the Keep window. N-N-C has an OCCURS field with a value of 1. The KEEP command for N-N-C did not specify an occurrence, so the default of 1 was used. The Autokeep window displays data name N-CNTR with an OCCURS field showing a value of I=4.

The I=4 indicates that the current N-CNTR element being displayed is associated with an index which currently points to the fourth element. The statement that encountered the after breakpoint contained N-CNTR(TX), which generated this information.

If you want to display the currently referenced data in a table as the subscript or index changes, enter the KEEP command using a data item qualified with the occurrence variable.

For instance, a KEEP on N-CNTR displays the data value in the window defaulting to the first occurrence (See the following figure), whereas a KEEP on N-CNTR(TX) displays the currently referenced data (Result of Entering the KEEP Command on a Table Element N-CNTR(TX)).

Result of Entering the KEEP Command on a Table Element N-CNTR

1                      OCCURS
 000027 K 10 N-CNTR                         >  0000                  DECIMAL


Result of Entering the KEEP Command on a Table Element N-CNTR(TX)

I=3                    OCCURS
 000027 K 10 N-CNTR                         >  0001                  DECIMAL


The value in the OCCURS field (I=3) can be typed over with a numeric index value to display a different table entry. Also, an occurrence modifier can be appended to the disassociated occurrence field in order to browse through the table elements each time Enter is pressed.

As shown in the following figure, add a signed integer (for example, +1, -2) to increment or decrement the index by a specified interval.

Browsing Through the Table Elements

                                                3+1                    OCCURS
                                               ----+----1----+----2----+
 000024 K 05 N-N-C                          >  SCALENE TRIANGLES    0001


The subscript and index boundaries are automatically checked when you are browsing through the table. The boundary limit can be displayed by entering the SHOW INDEX command. The following figure shows the boundary limits for N-N-C.

Result of the SHOW INDEX Command

------------------------------ CODE DEBUG TSO - SHOW --------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM:  TRIMAIN    MODULE: TRIMAIN  COMP DATE: 07/28/1996  COMP TIME: 12:15:45
------    ------------------------------------------- Before TRIMAIN/AMODE 24 ->
****************************** TOP OF DATA *************************************
N-N-C                       IN TRIMAIN                             LIMIT       4
INDEXED BY TX                                                     ENTRY       1
***************************** BOTTOM OF DATA ***********************************

Using the PEEK Command

You can enter the PEEK primary command with the name of the variable or you can enter the P line command either in the Procedure Division (where the variable is referenced) or in the Data Division (where the variable is defined).

There are three forms of the PEEK command, each corresponding to a data display format. The three forms are:

PEEK (P line command)

Displays the value of a variable.

PEEKE (PE line command)

Displays the values of the elementary items that are part of a group item.

PEEKH (PH line command)

Displays the hexadecimal values of a variable.

Examples of the commands and the resulting formats are described as follows

Use the DELETE primary command or line commands to remove the display resulting from the PEEK commands.

When the PEEK command is issued, the value of the variable is displayed in character or numeric format. Tables are formatted by each dimension when the PEEK command is entered at the elementary level. If the data displayed is a character data type, a column template is displayed to show the length. The length of a numeric item, however, is a function of the internal format.

The following figure shows the result of entering the PEEK command on WORK-REC in the TRIMAIN program.

Result of Entering PEEK WORK-REC

                                                     ---
 000030 P  01  WORK-REC                          >  345
 000031        05  SIDE-A               PIC 9(01).
 000032        05  SIDE-B               PIC 9(01).
 000033        05  SIDE-C               PIC 9(01)


The following figure shows the result of entering the PEEK command on N-N-C-TABLE in the TRIMAIN program. Note the MORE-> sign in the statement number area and the column template.

Result of Entering PEEK N-N-C-TABLE (Shows MORE>Sign and Column Template)

                                            ----+----1----+----2----+----3
 MORE-> P  01  N-N-C-TABLE         REDEF >  EQUILATERAL TRIANGLES....ISOSC
 000024        05  N-N-C           OCCURS 4 TIMES
 000025                            INDEXED BY TX.
 000026            10  N-NAME      PIC X(21).
 000027            10  N-CNTR      PIC 9(04).


The following figure shows the result of entering the PEEK command on N-N-C in the TRIMAIN program. Note the appearance of the OCCURS field. Because the OCCURS field is disassociated, it can be increased or decreased by simply overtyping the value.

Result of Entering PEEK N-N-C (Shows OCCURS Field and Column Template)

                                           1                         OCCURS
                                            ----+----1----+----2----+
 000024 P      05  N-N-C           OCCUR >  EQUILATERAL TRIANGLES....
 000025                            INDEXED BY TX.
 000026            10  N-NAME      PIC X(21).
 000027            10  N-CNTR      PIC 9(04).


The following figure shows the result of entering the PEEK command on CHECK-SUM in a program that contains counters and sums. Note that the numeric value is shown in PACKED decimal format.

Result of Entering PEEK CHECK-SUM (Shows PACKED Decimal Format)

  000252    01  WS-SUMS.
 000254 P      05  CHECK-SUM                >  +2001474.01            PACKED


The following figure shows the result of entering the PEEK command on CHAR-PTR in a program that contains halfwords. Note that the numeric value is shown in HALFWORD format.

Result of Entering PEEK CHAR-PTR (Shows HALFWORD Format)

  000260    01  WS-POINTERS
 000262 P      05  CHAR-PTR                  >  +093                HALFWORD


When the PEEKE command is entered for a group level data name containing elementary data items, the values for each elementary item are displayed, as shown in the following figure, where PEEKE was entered on WORK-REC in the TRIMAIN program.

Result of Entering PEEKE Command on the Group Level Data Item WORK-REC

Description:(Shows DECIMAL Format)

  000030    01  WORK-REC
 000031 P      05  SIDE-A              PIC 9 >  3                    DECIMAL
 000032 P      05  SIDE-B              PIC 9 >  4                    DECIMAL
 000033 P      05  SIDE-C              PIC 9 >  5                    DECIMAL


The PEEKH command displays the value of the variable in the hexadecimal format. The following figure shows the result of entering the PEEKH command on the 05 data item SIDE-A for the 01 data item WORK-REC in the TRIMAIN program.

Result of Entering PEEKH Command on the Group Data Item SIDE-A

Description:(Shows HEXADECIMAL Format)

  000031 P      05  SIDE-A              PIC 9 >  3                     DECIMAL
                                                 F
                                                3
 000032        05  SIDE-B              PIC 9(01).
 000033        05  SIDE-C              PIC 9(01).

The Session Log Entries for PEEK, KEEP, and Automatic KEEP

Every time a PEEK or KEEP command is entered, or an Automatic Keep displays data in the Keep window, the command and the value of the data name are entered in the session log. The format of the session log entry for both the PEEK and KEEP commands is similar.

To reduce the size of the session log, you can turn off the session log entries of the KEEP and PEEK commands and Automatic Keeps by using the SET LOG KEEP OFF, SET LOG PEEK OFF, and SET LOG AUTOKEEP OFF commands.

Since a displayed field is not scrollable in the session log, large alphanumeric items wrap around to the next line. The number of characters of data per line for an alphanumeric display is determined by the value specified on the SET LOGSIZE command. The record length for the session log file can be set to either 80 or 133. If the LOGSIZE is 80, an alphanumeric display wraps around after 30 characters per line. If the LOGSIZE is 133, the display wraps around after 80 characters per line.

The following figure shows a session log entry for the PEEK command entered for a table. The LOGSIZE is set to 80. In this example, the values in the displayed table wrap around every 30 bytes until the entire table of 100 bytes is displayed.

The Session Log Entry Following Execution of a PEEK Command

-------------------------------- CODE DEBUG TSO - LOG -------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM:  TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME:12:15:45
----------------------------------------------------- Before TRIMAIN/AMODE 24 ->
  XPED TSO SPF
  TEST TRIMAIN
XPD4170 RA417      CEE COBOL TRAP OPTION WAS FORCED TO OFF
*** TRIMAIN   FROM XT.SLS61.LINKLIB                           LINK 07/28/1996
  BEFORE TRIMAIN::TRIMAIN:
  AFTER  TRIMAIN::TRIMAIN:
PAUSE BEFORE TRIMAIN
BEFORE BREAKPOINT ENCOUNTERED
  PEEK NAME-N-CNTR-TABLE
                                             ----+----1----+----2----+----3
  000014 01  NAME-N-CNTR-TABLE            >  EQUILATERAL TRIANGLES....ISOSC
                                             ----+----4----+----5----+----6
                                          >  ELES TRIANGLES  ....SCALENE TR
                                             ----+----7----+----8----+----9
                                          >  IANGLES    ....INVALID TRIANGL
                                             ----+---10
                                          >  ES    ....
****************************** BOTTOM OF DATA ********************************

Unless SET HEXMODE is specified as ON, the session log entry of a displayed field containing nonrepresentable characters includes the symbol used to represent them—either periods or the character designated by the SET NONDISP command.

When the SET HEXMODE command is on, nonrepresentable characters are displayed in hexadecimal format in the session log. SET HEXMODE ON ensures that sufficient information is provided for a variable containing unprintable characters. All invalid numeric data (e.g., uninitialized packed data) is represented by question marks (?).

When an after, before, onetime, trace, when, or GO 1 breakpoint is encountered and the value of one or more of the kept variables changes, all kept variables are entered in the session log. The variables whose values have changed are listed first, followed by the data names that have not changed. If none of the values of the kept variables change, a session log entry is not made.

Using the MOVE Command

You can change the contents of program variables at any time using the MOVE command. MOVE lets you move either a data name or a literal into another data name.

There are three ways to enter the MOVE command:

  1. By typing over a displayed or kept field with a new value, causing an implicit move.
  2. Directly as a primary command.
  3. In conjunction with the INSERT command.

The session log entry for all three MOVE command formats is the same.

The following figures show examples of entering the MOVE command in different ways to produce the same result. The examples will use the following figure in which the variable WORK-REC is displayed.

Displaying Variable WORK-REC Prior to Typing Over Value

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
                                                -
000028   01 OUT-OF-RECS                       >  N
        ** END **

------   ----------------------------------------- Before TRIMAIN:49/AMODE 24 <>
                                               ---
000030 P  01  WORK-REC.                      >  345
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.


Example 1 — Typing Over Value in Variable Field to Cause an Implicit Move:

In the following figure, the displayed value (345) for the variable WORK-REC is typed over with the new value (999), causing an implicit move.

Typing Over Value for Variable WORK-REC

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
                                                -
000028   01 OUT-OF-RECS                       >  N
        ** END **

------   ----------------------------------------- Before TRIMAIN:49/AMODE 24 <>
                                               ---
000030 P  01  WORK-REC.                      >  999
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.


Example 2 — Entering MOVE as a Primary Command:

If you enter MOVE '345’ TO WORK-REC in the primary command line, the result is an explicit move. As shown in the following figure, the literal value (345) is moved to the data field for WORK-REC and the value of WORK-REC is changed from 999 to 345.

An Example of MOVE Entered as a Primary Command

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
                                                -
000028   01 OUT-OF-RECS                       >  N
        ** END **

------   ----------------------------------------- Before TRIMAIN:49/AMODE 24 <>
                                               ---
000030 P  01  WORK-REC                       >  345
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.


Example 3 — Using the MOVE Command in Conjunction With the INSERT Command:

In the following figure, the I (Insert) line command was entered on line 49 to open up a line on which to insert the MOVE command. A before breakpoint is also being entered on line 50, following the inserted MOVE command.

Inserting MOVE Command

 ------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
        ** END **



------   -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000047           AT END
000048           MOVEYTO OUT-OF-RECS.
000049        IF OUT-OF-RECS =N
’’’’’’           move999to work-rec
B  050           MOVE ZERO TO TRIANGLE-TYPE
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE


When you press Enter, a before breakpoint is indicated for line 50, as shown in the following figure.

Before Breakpoint Set on Line 50

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                                1 COMMAND(S) COMPLETED
        ** END **



------   -------------------------------------------- Before TRIMAIN/AMODE 24 <>
000047           AT END
000048           MOVEYTO OUT-OF-RECS.
000049        IF OUT-OF-RECS =N
’’’’’’           MOVE999TO WORK-REC
000050 B         MOVE ZERO TO TRIANGLE-TYPE
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE


Then, when you press PF12 (GO), execution is paused following the inserted MOVE command as shown in the following figure.

Source Display After GO is Entered

------------------------------ CODE DEBUG TSO - SOURCE ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
                          BEFORE BREAKPOINT ENCOUNTERED
000029   01 TRIANGLE-
TYPE                    >  ??                INVALID DECIMAL
        ** END **


------   ----------------------------------------- Before TRIMAIN:50/AMODE 24 <>
000047           AT END
000048           MOVEYTO OUT-OF-RECS.
000049        IF OUT-OF-RECS =N
’’’’’’           MOVE999TO WORK-REC
=====> B         MOVE ZERO TO TRIANGLE-TYPE
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE


Enter KEEP for WORK-REC. The value indicated on the inserted MOVE command is displayed in the Keep window as shown in the following figure.

Result of an Inserted MOVE Command

------------------------------ CODE DEBUG TSO - SOURCE -------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
                                              ---
000030 K 01 WORK-REC                        >  999
000029   01 TRIANGLE-TYPE                   >  ??                INVALID DECIMAL
        ** END **
------   ----------------------------------------- Before TRIMAIN:50/AMODE 24 <>
000047           AT END
000048           MOVEYTO OUT-OF-RECS.
000049        IF OUT-OF-RECS =N
’’’’’’           MOVE999TO WORK-REC
=====> B         MOVE ZERO TO TRIANGLE-TYPE
000051           CALLTRITSTUSING WORK-REC TRIANGLE-TYPE

Displaying and Modifying Memory and Registers

Storage areas and general-purpose registers can be accessed if you wish to debug at the hexadecimal level. The MEMORY command lets you view and modify the storage area starting from a specified location. A full screen memory display is shown in the dump format, and any unprotected areas can be typed over to alter the storage content. The GPREGS command lets you view and modify the registers. A register window is displayed at the bottom of the screen, and you can type over the hexadecimal values to modify the registers. The TOGGLE command permits you to switch back and forth between the storage screen (generated from the MEMORY command) and the listing screen (general-purpose registers opened by using the GPREGS command).

Using the MEMORY Command

The MEMORY command entered without any arguments displays the storage area, starting from the beginning of the currently displayed program. For example, entering the following command from the primary command line of the TRIMAIN program displays the Memory Display screen shown in following figure:

   MEMORY

The fourth line on the Memory Display screen contains the base address and a column template that starts with zero and continues to hexadecimal F. The offsets below the base address list the displacement from the start of the storage area.

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

Result of Entering the MEMORY Command

------------------------------ CODE DEBUG TSO - MEMORY ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
----------------------------------------------------- Before TRIMAIN/AMODE 24 --
BASE = 00093038   0 - 2 -   4 - 6 -   8 - A -   C - E -    =  0-2-4-6-8-A-C-E-
******************************* TOP OF DATA *********************************
  000000   ===>  90ECD00C  185D05F0  4580F010  E3D9C9D4   =  ..}..).0..0.TRIM
  000010   ===>  C1C9D540  E5E2D9F1  0700989F  F02407FF   =  AIN VSR1....0...
  000020   ===>  96021034  07FE41F0  000107FE  0009E7DA   =  .......0......X.
  000030   ===>  0009E038  0009E038  0009E4E0  0009E278   =  ..\...\...U\..S.
  000040   ===>  0009E544  0009E79A  00000000  00000000   =  ..V...X.........
  000050   ===>  00000000  00000000  00000000  00000000   =  ................
  000060   ===>  00000000  00000000  00000000  00000000   =  ................
  000070   ===>  00000000  00000000  00000000  00000000   =  ................
  000080   ===>  00000000  00000000  F1F24BF5  F44BF2F6   =  ........12.54.26
  000090   ===>  E2C5D740  F2F86B40  F1F9F9F4  00000000   =  SEP 28, 1994....
  0000A0   ===>  C5D8E4C9  D3C1E3C5  D9C1D340  E3D9C9C1   =  EQUILATERAL TRIA
  0000B0   ===>  D5C7D3C5  E2000000  00C9E2D6  E2C3C5D3   =  NGLES....ISOSCEL
  0000C0   ===>  C5E240E3  D9C9C1D5  C7D3C5E2  40400000   =  ES TRIANGLES  ..
  0000D0   ===>  0000E2C3  C1D3C5D5  C540E3D9  C9C1D5C7   =  ..SCALENE TRIANG
  0000E0   ===>  D3C5E240  40404000  000000C9  D5E5C1D3   =  LES    ....INVAL
  0000F0   ===>  C9C440E3  D9C9C1D5  C7D3C5E2  40404040   =  ID TRIANGLES
  000100   ===>  00000000  00000000  00000000  00000000   =  ................
  000110   ===>  00000000  00000000  00000000  00000000   =  ................


The MEMORY command can be entered with indirect register addressing to specify a location. For example, the following command displays memory starting from the location pointed to by the 24-bit mode address in register 13, as seen in the following figure:

   MEMORY R13%

Result of Entering MEMORY R13%

------------------------------ CODE DEBUG TSO - MEMORY ------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
----------------------------------------------------- Before TRIMAIN/AMODE 24 --
BASE = 00093278   0 - 2 -   4 - 6 -   8 - A -   C - E -    =  0-2-4-6-8-A-C-E-
******************************** TOP OF DATA ********************************
  000000   ===>  00300000  00096B68  00000000  00000000   =  ......,.........
  000010   ===>  00000000  00000000  00000000  00000000   =  ................
  000020   ===>  00000000  00000000  00000000  00000000   =  ................
  000030   ===>  00000000  00000000  00000000  00000000   =  ................
  000040   ===>  00000000  00000000  3102A04B  00000000   =  ................
  000050   ===>  00000000  00093544  00000000  00000000   =  ................
  000060   ===>  00000000  00093880  00093A6E  00000000   =  ...........>....
  000070   ===>  50093854  8008BBFC  0005C5F8  00093786   =  &.........E8....
  000080   ===>  50093838  000930D8  00000000  00093488   =  &......Q........
  000090   ===>  000937DA  00093038  00093038  000934E0   =  ...............\
  0000A0   ===>  00000000  00000000  00000000  00000000   =  ................
  0000B0   ===>  00000000  00000000  00000000  00000000   =  ................
  0000C0   ===>  00000000  00000000  00000000  00000000   =  ................
  0000D0   ===>  00000000  00000000  00000000  00000000   =  ................
  0000E0   ===>  00000000  00000000  00000000  00000000   =  ................
  0000F0   ===>  00000000  00000000  00000000  00000000   =  ................
  000100   ===>  00000000  00000000  00000000  00000000   =  ................
  000110   ===>  00000000  00000000  00000000  00000000   =  ................


Also, you can use arithmetic expressions such as the following to access storage, as shown in the following figure.

MEMORY R9%+4

Result of Entering MEMORY R9%+4

------------------------------ CODE DEBUG TSO - MEMORY ---------------------------
COMMAND ===>                                                     SCROLL===> CSR
PROGRAM: TRIMAIN    MODULE: TRIMAIN   COMP DATE: 07/28/1996  COMP TIME: 12:15:45
----------------------------------------------------- Before TRIMAIN/AMODE 24 --
BASE = 000937DA   0 - 2 -   4 - 6 -   8 - A -   C - E -    =  0-2-4-6-8-A-C-E-
******************************* TOP OF DATA *********************************
  000004   ===>  D04847E0  F0165800  B048982D  B05058E0   =  }..\0........&.\
  000014   ===>  D05407FE  9620D048  41600004  4110C000   =  }.....}..-....{.
  000024   ===>  4170C003  05505840  10001E4B  50401000   =  ..{..&. ....& ..
  000034   ===>  87165000  4110C028  4170C02F  05505840   =  ..&...{...{..&.
  000044   ===>  10001E4B  50401000  87165000  41600008   =  ....& ....&..-..
  000054   ===>  4110C030  4170C047  05505840  10001E4B   =  ..{...{..&. ....
  000064   ===>  50401000  87165000  4180D200  41600004   =  & ....&...K..-..
  000074   ===>  4170D20F  05105800  80001200  47801010   =  ..K.............
  000084   ===>  1E0B5000  80008786  10005860  D2045870   =  ..&........-K...
  000094   ===>  D200D217  D238C030  58F0C008  05EF002C   =  K.K.K.{..0{.....
  0000A4   ===>  000158E0  D05407FE  00008000  00000009   =  ...\}...........
  0000B4   ===>  3278C9D3  C2D6D5E3  D9F00000  00000000   =  ..ILBONTR0......
  0000C4   ===>  00000000  00000000  00000000  00000000   =  ................
  0000D4   ===>  00000000  00000000  00000000  00000000   =  ................
  0000E4   ===>  00000009  426A0000  00000000  00000000   =  .....|..........
  0000F4   ===>  00000000  00000000  00000000  00000000   =  ................
  000104   ===>  00000000  00000000  00000000  00000000   =  ................
  000114   ===>  00000000  00000000  00000000  00000000   =  ................


Using the GPREGS Command

The GPREGS command opens a window and displays the 16 general-purpose registers at the bottom of the screen. The following figure shows the result of entering the GPREGS command for the TRIMAIN program. The displayed hexadecimal values can be typed over to change the register contents.

Result of Entering the GPREGS Command

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
 GPREGS  R0  ==> 70043C2E  R1  ==> 50043FCE  R2  ==> 00043210  R3  ==> 00043BB8
         R4  ==> 00043E8A  R5  ==> 50043FB2  R6  ==> 00043790  R7  ==> 00000000
         R8  ==> 00043B40  R9  ==> 00043F54  R10 ==> 000436F0  R11 ==> 000436F0
         R12 ==> 00043B98  R13 ==> 00043930  R14 ==> 00043C2C  R15 ==> 0009E5DE

The register window can be removed from display by entering the following command:

GPREGS OFF

Using the TOGGLE Command

The TOGGLE command lets you switch from one panel display to another. For COBOL, you may move back and forth between the Listing screen and the Storage screen. It may be beneficial for you to define a specific PF KEY to efficiently utilize the toggle functionality.

 

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