Library View Topics Framed Contents Revised Topics Previous Topic Next Topic Search Search ResultsPrevious Topic MatchNext Topic Match Notes List Notes Print Download No PDF Handheld DisconnectedHandheld ConnectedHelp

X 8.1.9 READY or RESET TRACE Statement




X The READY or RESET TRACE statement can only appear in the Procedure
X Division, but has no effect on your program.


 X  ___ Format _____________________________________________________________ 
 X |                                                                        |
 X | >>__ _READY_ __TRACE__._____________________________________________>< |
 X |     |_RESET_|                                                          |
   |                                                                        |
   |________________________________________________________________________|

X You can reproduce the function of READY TRACE by using the USE FOR
X DEBUGGING declarative, DISPLAY statement, and DEBUG-ITEM special register.
X For example:


 X               .
 X               .
 X      ENVIRONMENT DIVISION.
 X        CONFIGURATION SECTION.
 X        SOURCE-COMPUTER. IBM-390 WITH DEBUGGING MODE.
 X               .
 X      DATA DIVISION.
 X               .
 X        WORKING-STORAGE SECTION.
 X        01 TRACE-SWITCH        PIC 9 VALUE 0.
 X           88  READY-TRACE           VALUE 1.
 X           88  RESET-TRACE           VALUE 0.
 X               .
 X      PROCEDURE DIVISION.
 X        DECLARATIVES.
 X        COBOL-II-DEBUG SECTION.
 X          USE FOR DEBUGGING ON ALL PROCEDURES.
 X        COBOL-II-DEBUG-PARA.
 X          IF READY-TRACE THEN
 X              DISPLAY DEBUG-NAME
 X          END-IF.
 X        END DECLARATIVES.
 X        MAIN-PROCESSING SECTION.
 X               .
 X        PARAGRAPH-3.
 X               .
 X          SET READY-TRACE TO TRUE.
 X        PARAGRAPH-4.
 X               .
 X        PARAGRAPH-6.
 X               .
 X          SET RESET-TRACE TO TRUE.
 X        PARAGRAPH-7.


X where DEBUG-NAME is a field of the DEBUG-ITEM special register that
X displays the procedure-name causing execution of the debugging procedure.
X (In this example, the object program displays the names of procedures
X PARAGRAPH-4 through PARAGRAPH-6 as control reaches each procedure within
X the range.)


X At run time, you must specify the DEBUG run-time option to activate this
X debugging procedure. In this way, you have no need to recompile the
X program to activate or deactivate the debugging declarative.

Previous Topic Next Topic © Copyright IBM Corp. 1991, 1998

IBM Library Server Copyright 1989, 2005 IBM Corporation. All rights reserved.





Return to library:   z/OS | z/OS.e | TPF | z/VSE | z/VM | IBM Hardware | IBM System z Redbooks
Glossary:   IBM terminology
Publications:   How to order publications
Readers:   Download IBM Library Reader | Download IBM Softcopy Reader | Download Adobe® Acrobat® Reader®
Library management:   Download IBM Softcopy Librarian
Contacts:   Contact z/OS


Adobe, the Adobe logo, Acrobat, the Acrobat logo, and Acrobat Reader are registered trademarks of Adobe Systems incorporated.