HP 3000 Manuals

Using Debug (continued) [ HP COBOL II/XL Programmer's Guide ] MPE/iX 5.0 Documentation


HP COBOL II/XL Programmer's Guide

Using Debug (continued) 

Debugging Trap Errors 
[REV BEG]

Invalid Decimal Data in NUMERIC Class Condition.   

This example shows how you can force the NUMERIC class condition on
packed decimal data to be true in certain cases where it would otherwise
be false.  By specifying I in column 9 of COBRUNTIME, any NUMERIC class
condition on packed decimal data is true in the following cases:

   *   A signed value in an unsigned PACKED-DECIMAL field.
   *   An unsigned value in a signed PACKED-DECIMAL field.
   *   Any invalid sign nibble.

This matches the behavior of HP COBOL II/V programs.  Unless you put I in
column 9 of COBRUNTIME, the above conditions cause any NUMERIC class
condition to be false.

The following is an example program that contains invalid packed decimal
data:

     WORKING-STORAGE SECTION.
     01  DECIMAL-NO-SIGN   PIC 9(3) USAGE PACKED-DECIMAL VALUE 123.
     01  DECIMAL-SIGN    REDEFINES DECIMAL-NO-SIGN
                           PIC S9(3) USAGE PACKED-DECIMAL.
     PROCEDURE DIVISION.
     PARA-001.
         DISPLAY "DECIMAL-NO-SIGN is ", DECIMAL-NO-SIGN.
         DISPLAY "DECIMAL-SIGN is ", DECIMAL-SIGN.
         IF DECIMAL-NO-SIGN IS NUMERIC
             DISPLAY "DECIMAL-NO-SIGN is NUMERIC."
         ELSE DISPLAY "DECIMAL-NO-SIGN is not NUMERIC."
         END-IF.
         IF DECIMAL-SIGN IS NUMERIC
             DISPLAY "DECIMAL-SIGN is NUMERIC."
         ELSE DISPLAY "DECIMAL-SIGN is not NUMERIC."
         END-IF.
         STOP RUN.

When this program is compiled and run in Native Mode with column 9 of
COBRUNTIME set to anything but I, the program displays the following:

     DECIMAL-NO-SIGN is 123            
     DECIMAL-SIGN is +123              
     DECIMAL-NO-SIGN is NUMERIC.
     DECIMAL-SIGN is not NUMERIC.     DECIMAL-SIGN contains an invalid sign. 

[REV END]

[REV
BEG]

When this program is compiled and run either in Native Mode with column 9
of COBRUNTIME set to I, or in Compatibility Mode, it displays the
following:

     DECIMAL-NO-SIGN is 123           
     DECIMAL-SIGN is +123             
     DECIMAL-NO-SIGN is NUMERIC.
     DECIMAL-SIGN is NUMERIC.        Invalid sign still makes NUMERIC test true. 

The following diagram shows the contents of the single data item named by
DECIMAL-NO-SIGN and redefined by DECIMAL-SIGN. The values shown are
hexadecimal.  Each box in the diagram represents one packed-decimal
digit, which is 4 bits:

-------------------------------------------------------------------------------------------------
-           1           -           2           -           3           -           F           -
-------------------------------------------------------------------------------------------------

The rightmost position is the sign of the data value.  The F in this
position means the value is unsigned.  Any valid signed PACKED-DECIMAL
data has either the hexadecimal value C for a positive value, or D for a
negative value, in the rightmost 4 bits.  For more information, see the
section "USAGE IS PACKED-DECIMAL or COMPUTATIONAL-3" in Chapter 7  of
the HP COBOL II/XL Reference Manual.[REV END]
[REV BEG]

Traps with COBOL Functions.   

In the following example, the parameter for the FACTORIAL function is out
of range.

      00001          000100$control post85
      00001          001000 identification division.
      00002          001100 program-id. trap-fact.
      00003          001200 data division.
      00004          001300 working-storage section.
      00005          001400 01  n                    pic s9(18) comp.
      00006          001500 01  bad-value            pic s999 comp value -1.
      00007          001600 procedure division.
      00008          001700 p1.
      00009          001800*********************************************
      00010          001900* factorial(-1) with no size error phrase.  *
      00011          002000*********************************************
      00012          002100     display "should give no size error phrase"
      00013          002200     compute n = function factorial(bad-value)
      00014          002300     display "test case did not abort".

When run, the following is output:

     should give no size error phrase
     No SIZE ERROR phrase (COBERR 747)
     Program file: $OLDPASS.PUBS.COBOL74
     Trap type = 80000000 (00,00), at pc = 0000035D.000053C7
     assertion trap
     DEBUG/XL A.47.01

     HPDEBUG Intrinsic at: 118.00351270 cob_trap.print_message+$5c4
     $$$$ Trap occurred at: trap_fact+$6c, at Stmt    #13
          PC=35d.000053c4 trap_fact+$6c
     * 0) SP=4033a0c8 RP=35d.00000000
          (end of NM stack)
     ============================================================

[REV END]

[REV
BEG]

In the next example, for a function that uses a procedure in the Compiler
Library, an invalid parameter is detected by the Compiler Library
routine.  The Compiler Library routine generates the math library error
message and the COBOL trap handler provides the statement number of the
source line that produced the trap.

      00001          000100$control post85
      00001          001000 identification division.
      00002          001100 program-id. trap-sqrt.
      00003          001200 data division.
      00004          001300 working-storage section.
      00005          001400 01  n                    pic s999v999 comp.
      00006          001500 01  bad-value            pic s999 comp value -1.
      00007          001600 procedure division.
      00008          001700 p1.
      00009          001800*********************************************
      00010          001900* sqrt(-1) with no size error phrase.       *
      00011          002000*********************************************
      00012          002100     display "should give no size error phrase"
      00013          002200     compute n rounded = function sqrt(bad-value)
      00014          002300     display "test case did not abort".

When run, the following is output:

     should give no size error phrase
     No SIZE ERROR phrase (COBERR 747)
     Program file: $OLDPASS.PUBS.COBOL74
     Library trap type = 0000000B (11)
     DEBUG/XL A.47.01

     HPDEBUG Intrinsic at: 7a0.00016ec4 cob_trap_lib.print_message+$158
     $$$$ Call occurred at: trap_sqrt+$68, at Stmt    #13
          PC=7a0.00016ec4 cob_trap_lib.print_message+$158
       0) SP=4033a480 RP=7a0.00017014 COB_TRAP_LIB+$a8
       1) SP=4033a428 RP=7a0.0000d504 COB_TRAP_LIB+$8
            export stub: 109.00377d14 FTN_GETLIBTRAP+$6c
       2) SP=4033a250 RP=109.00377c74 ?FTN_GETLIBTRAP+$8
            export stub: 109.005b1ddc DINVALIDERR+$e4
       3) SP=4033a1d8 RP=109.005b12bc _dsqrterr+$1c
       4) SP=4033a158 RP=109.005b0c98 label2+$10
       5) SP=4033a128 RP=109.005b0b84 ?FTN_DSQRT$+$8
            export stub: 308.00005398 trap_sqrt+$68
     * 6) SP=4033a0d0 RP=308.00000000
          (end of NM stack)
     ============================================================
     *** MATH LIBRARY ERROR 28: DSQRT(X): X < 0.0 OR X = NaN
[REV END]

[REV
BEG]

The next example shows an IEEE floating point error.

      00001          001000$control post85
      00001          001100 identification division.
      00002          001200 program-id. trap-float-zero.
      00003          001300 data division.
      00004          001400 working-storage section.
      00005          001500 01  n                    pic s999v999 comp.
      00006          001600 01  bad-value            pic s999 comp value zero.
      00007          001700 procedure division.
      00008          001800 p1.
      00009          001900*********************************************
      00010          002000* divide by zero with no size error phrase. *
      00011          002100*********************************************
      00012          002200     display "should give no size error phrase".
      00013          002300     compute n rounded = 1 / function sin(bad-value)
      00014          002400     display "test case did not abort".

When run, the following is output:

     should give no size error phrase
     No SIZE ERROR phrase (COBERR 747)
     Program file: $OLDPASS.PUBS.COBOL74
     Trap type = 00020000 (14,27), at pc = 0000035D.000053B7
     ieee divide by 0        DIV
             operand 1 = 3FF0000000000000
             operand 2 = 0000000000000000
             result    = 47C3500000000000
     DEBUG/XL A.47.01

     HPDEBUG Intrinsic at: 118.00351270 cob_trap.print_message+$5c4
     $$$$ Trap occurred at: trap_float_zero+$7c, at Stmt    #13
          PC=35d.000053b4 trap_float_zero+$7c
     * 0) SP=4033a0d0 RP=35d.00000000
          (end of NM stack)
     ============================================================
[REV END]

Trace Traps.   

Trace traps are "global" breakpoints that are easy to set up and use,
providing a very useful tool for quickly isolating program problems
within Debug.

Trace traps are global in that they apply to all paragraphs and sections,
entry and/or exit points.  The COBOL compiler generates them within an
object program, and once generated, they can be armed and used with Debug
on MPE XL.

To use trace traps with your program:

   1.  Compile your program with the control option SYMDEBUG. This causes
       the compiler to generate trace trap breakpoints in your code.[REV
       BEG] (Note that these breakpoints are not available if the
       SYMDEBUG=XDB option is specified.)[REV END]

   2.  Arm the trace trap breakpoints with the Debug command TRAP (see
       the syntax that follows).

Syntax.   

Type the underlined part in response to the Debug prompt.

     $nmdebug> TRAP [trap_name]  [option] 

Parameters.   

trap_name                 One of the following:

                          BEGIN_PROCEDURE  Stops the program at the entry
                                           to each procedure.  For a
                                           COBOL program, "procedure"
                                           means program.

                          END_PROCEDURE    Stops the program at the exit
                                           from each procedure.  For a
                                           COBOL program, "procedure"
                                           means program.

                          LABELS           Stops the program at every
                                           section and paragraph.

                          EXIT_PROGRAM     Stops the program at program
                                           exit point.  For a COBOL
                                           program, this is usually the
                                           STOP RUN statement.

                          ENTER_PROGRAM    Stops the program at the
                                           program entry point.

                          TRACE_ALL        All of the above.

option                    One of the following:

                          LIST             List the current setting of
                                           trap_name.  This is the
                                           default.

                          ARM              Arm the trap specified by
                                           trap_name.

                          DISARM           Disarm the trap specified by
                                           trap_name.

Example.   

If you type the underlined command in response to the Debug prompt, the
program stops at every section and paragraph.

     $nmdebug> TRAP LABELS ARM 


NOTE [REV BEG] The SYMDEBUG=TOOLSET control option significantly increases the amount of object code and execution time[REV END] for your program, so use it only while you are debugging your program. When the program works, recompile it without SYMDEBUG.


MPE/iX 5.0 Documentation