Top
NetCOBOL V11.0 Debugging Guide
FUJITSU Software

5.2.3 Examples of Using the CHECK Function

Checking Reference Modification

Program A

000000 @OPTIONS CHECK(BOUND)
          :
000500 77 data-1                   PIC X(12).                       
000600 77 data-2                   PIC X(12).                      
000700 77 length-to-be-referenced  PIC 9(4) BINARY.
          :
001100    MOVE 10   TO  length-to-be-referenced.                         
001200    MOVE data-1 (1:length-to-be-referenced)                        
           TO  data-2 (4:length-to-be-referenced).
          :

The following message is written for data-2 when the MOVE statement on line 1200 is executed:

JMP0821I-E/U  [PID:xxxxxxxx TID:xxxxxxxx] REFERENCE MODIFIER IS OUT OF RANGE.  PGM=A. LINE=1200.1. OPD=data-2.

Checking Subscripts and Indexes

Program A

000000 @OPTIONS CHECK(BOUND)
            :
000500 77      subscript  PIC S9(4).                             
000600 01  d    table.                                           
000700   02 table-1 OCCURS 10 TIMES INDEXED BY index-1.           
000800      03  element-1  PIC X(5).
            :
001100           MOVE  15  TO  subscript.                          
001200           ADD    1  TO  element-1(subscript).               
001300           SET   index-1  TO  0.                            
001400           SUBTRACT  1  FROM  element-1(index-1).           
            :

When the ADD/SUBTRACT statement is executed, the following message is written:

JMP0820I-E/U  [PID:xxxxxxxx TID:xxxxxxxx] SUBSCRIPT/INDEX IS OUT OF RANGE.  PGM=A. LINE=1200.1. OPD=element-1
JMP0820I-E/U  [PID:xxxxxxxx TID:xxxxxxxx] SUBSCRIPT/INDEX IS OUT OF RANGE.  PGM=A. LINE=1400.1. OPD=element-1

Checking Target Words of the OCCURS DEPENDING ON Clause

Program A

000000 @OPTIONS CHECK(BOUND)
    :
000050 77      subscript      PIC S9(4).                                
000060 77      cnt            PIC S9(4).                                
000070 01      dtable.                                                  
000080  02 table-1 OCCURS 1 TO 10 TIMES DEPENDING ON cnt.            
000090          03  element-1  PIC X(5).                                 
    :
000110         MOVE   5  TO  subscript.                                 
000120         MOVE  25  TO  cnt.                                       
000130         MOVE  "ABCDE"  TO  element-1(subscript).                 
    :

The following message is written for the count:

JMP0822I-E/U  [PID:xxxxxxxx TID:xxxxxxxx] ODO OBJECT VALUE IS OUT OF RANGE.  PGM=A. LINE=120.1. OPD=element-1. ODO=cnt.

Checking Numeric Data Exceptions

Program A

000000 @OPTIONS CHECK(NUMERIC)
   :
000050 01 CHAR PIC X(4) VALUE "ABCD".
000060 01 EXTERNAL-DECIMAL REDEFINES CHAR PIC S9(4).
000070 01 NUM PIC S9(4).
   :
000150    MOVE EXTERNAL-DECIMAL TO NUM.
   :

For EXTERNAL-DECIMAL, the following message will appear.

JMP08281-E/U [PID:xxxxxxxx TID:xxxxxxxx] INVALID VALUE SPECIFIED. PGM=A. LINE=150. OPD= EXTERNAL-DECIMAL

Checking a zero divisor

Program A

000000 @OPTIONS CHECK(NUMERIC)
   :
000060 01 DIVIDEND PIC S9(8) BINARY VALUE 1234.
000070 01 DIVISOR PIC S9(4) BINARY VALUE 0.
000080 01 RESULT PIC S9(4) BINARY VALUE 0.
   
000150    COMPUTE RESULT = DIVIDEND / DIVISOR.
   

For the DIVISOR, the following message will appear.

JMP08291-E/U  [PID:xxxxxxxx TID:xxxxxxxx] DIVIDED BY ZERO. PGM=A. LINE=150. OPD= DIVISOR 

Checking parameters for calling a method

Program A

000000 @OPTIONS CHECK(ICONF)
000010 PROGRAM-ID. A.
             :
000030 01 PRM-01 PIC X(9).
000040 01 0BJ-U USAGE IS OBJECT REFERENCE.
             :
000060    SET    OBJ-U TO B.
000070    INVOKE OBJ-U "C" USING BY REFERENCE PRM-01.

            Class B/Method C 
000010 CLASS-ID. B.
             :
000030 FACTORY.
000040 PROCEDURE DIVISION.
             :
000060 METHOD-ID.C.
             :
000080 LINKAGE SECTION.
000090 01 PRM-01 PIC 9(9) PACKED-DECIMAL.
000100 PROCEDURE DIVISION USING PRM-01.
             :

The following message is written when the INVOKE statement of program A is executed:

JMP08101-E/U [PID:xxxxxxxx TID:xxxxxxxx] FAILURE IN USING PARAMETER OF THE 'C' METHOD.  PARAMETER=1. PGM=A  LINE=70.1

Checking the program calling conventions

There are several calling conventions for Windows applications. The standard calling conventions and the specification method of the calling conventions depend on the development language.

NetCOBOL uses the CALL statement or the WITH phrase of the Procedure Division statement to determine which calling conventions are to be used when passing parameters. Refer to "Differences Among Calling conventions" in the "NetCOBOL User’s Guide".

If the calling conventions are different for the calling program and called program, an error will occur at linkage if the programs have a static-link structure or dynamic-link structure. For a dynamic program structure, however, an error will not occur at linkage. As a result, the execution-time stack is destroyed and the program terminates abnormally. In addition, if the calling conventions of the calling program are STDCALL, the program might terminate abnormally if the calling conventions are the same, but the number of parameters is different. Thus, the program might terminate abnormally for the same reason as if the calling conventions were different. Therefore, program calling conventions are an object for checking.


Program A

000000 @OPTIONS CHECK(LINKAGE)
000010 PROGRAM-ID. A.
             :
000030  01  PRM-01  PIC S9(9) COMP-5.
             :
000070     CALL "B" WITH C LINKAGE USING PRM-01.
             :

Program B(C functions)

#include <windows.h>
             :
int WINAPI B(long FAR* data1)   ...(*1)
{
             :
}

*1 For the following function declarations, the STDCALL calling conventions will be used.

       int WINAPI        function name()
       int CALLBACK      function name()
       int PASCAL        function name()
       int far pascal    function name()
       int _stdcall      function name()

The following message is written when the CALL statement of program A is executed:

JMP0811I-E/U [PID:xxxxxxxx TID:xxxxxxxx] FAILURE IN CALLING CONVENTIONS OR PARAMETERS OF THE 'B' PROGRAM. PGM=A LINE=7.1

Internal program call parameter investigation

Program A

000001 @OPTIONS CHECK(PRM)
000002 PROGRAM-ID. A.
000003 ENVIRONMENT DIVISION.
000004 CONFIGURATION SECTION.
000005 REPOSITORY.
000006     CLASS CLASS1.
000007 DATA DIVISION.
000008 WORKING-STORAGE SECTION.
000009 01 P1 PIC X(20).
000010 01 P2 PIC X(10).
000011 01 P3 USAGE OBJECT REFERENCE CLASS1.
000012 PROCEDURE DIVISION.
000013     CALL "SUB1" USING P1 P2            *> JMN3333I-S
000014     CALL "SUB2"                        *> JMN3414I-S
000015     CALL "SUB1" USING P1 RETURNING P2  *> JMN3508I-S
000016     CALL "SUB1" USING P2               *> JMN3335I-S
000017     CALL "SUB3" USING P3               *> JMN3334I-S
000018     EXIT PROGRAM.
000019*
000020 PROGRAM-ID. SUB1.
000021 DATA DIVISION.
000022 LINKAGE SECTION.
000023 01 L1 PIC X(20).
000024 PROCEDURE DIVISION USING L1.
000025 END PROGRAM SUB1.
000026*
000027 PROGRAM-ID. SUB2.
000028 DATA DIVISION.
000029 LINKAGE SECTION.
000030 01 RET PIC X(10).
000031 PROCEDURE DIVISION RETURNING RET.
000032 END PROGRAM SUB2.
000033*
000034 PROGRAM-ID. SUB3.
000035 DATA DIVISION.
000036 LINKAGE SECTION.
000037 01 L-OR1 USAGE OBJECT REFERENCE.
000038 PROCEDURE DIVISION USING L-OR1.
000039 END PROGRAM SUB3.
000040 END PROGRAM A.

When you compile program A, the following diagnostic message is output at the time of compilation.

** DIAGNOSTIC MESSAGE ** (A)
13: JMN3333I-S  THE NUMBER OF PARAMETERSPECIFIED IN USING PHRASE OF CALL STATEMENT MUST BE THE SAME NUMBER OF PARAMETER SPECIFIED IN USING PHRASE OF PROCEDURE DIVISION.
14: JMN3414I-S  RETURNING ITEM MUST BE SPECIFIED FOR CALL STATEMENT WHICH CALLS 'SUB2'. THERE IS RETURNING SPECIFICATION IN PROCEDURE DIVISION OF PROGRAM 'SUB2'.
15: JMN3508I-S  RETURNING ITEM MUST NOT BE SPECIFIED FOR CALL STATEMENT WHICH CALLS 'SUB1'. THERE IS NOT RETURNING SPECIFICATION IN PROCEDURE DIVISION OF PROGRAM 'SUB1'.
16: JMN3335I-S  THE LENGTH OF PARAMETER 'P2' SPECIFIED IN USING PHRASE OR RETURNING PHRASE OF CALL STATEMENT MUST BE THE SAME LENGTH OF PARAMETER 'L1' SPECIFIED IN PROCEDURE DIVISION USING PHRASE OR RETURNING PHRASE OF PROGRAM 'SUB1'.
17: JMN3334I-S  THE TYPE OF PARAMETER 'P3' SPECIFIED IN USING PHRASE OR RETURNING PHRASE OF CALL STATEMENT MUST BE THE SAME TYPE OF PARAMETER 'L-OR1' SPECIFIED IN PROCEDURE DIVISION USING PHRASE OR RETURNING PHRASE OF PROGRAM 'SUB3'.
STATISTICS: HIGHEST SEVERITY CODE=S, PROGRAM UNIT=1

External program call parameter investigation

In a program invocation, an error in passing parameters causes a program malfunction because the program refers to or updates an unexpected data item or area.

When a COBOL program compiled by specifying a CHECK(PRM) compile option calls another COBOL program compiled in the same way, a message is output if the lengths of each of the parameters do not match.

000010 @OPTIONS CHECK(PRM)
000020 IDENTIFICATION  DIVISION.
000030 PROGRAM-ID.     A.
000040 DATA            DIVISION.
000050 WORKING-STORAGE SECTION.
000060 01  USE-PRM01   PIC 9(04).
000070 01  USE-PRM02   PIC 9(04).
000080 01  RET-PRM01   PIC 9(04).
000090 PROCEDURE       DIVISION.
000100     CALL 'B' USING USE-PRM01 USE-PRM02
000110              RETURNING RET-PRM01.
000120 END PROGRAM     A.
000000 @OPTIONS CHECK(PRM)
000010 IDENTIFICATION  DIVISION.
000020 PROGRAM-ID.     B.
000030 DATA            DIVISION.
000070 LINKAGE         SECTION.
000080 01  USE-PRM01   PIC 9(08).
000090 01  USE-PRM02   PIC 9(04).
000100 01  RET-PRM01   PIC 9(04).
000120 PROCEDURE       DIVISION USING USE-PRM01 USE-PRM02
000130                          RETURNING RET-PRM01.
000140 END PROGRAM     B.

When the CALL statement in program A is executed, the following message is output:

[PID:xxxxxxxx TID:xxxxxxxx] FAILURE IN 'USING 1ST PARAMETER' OF CALL STATEMENT.  PGM=A. LINE=10.1.