bug-gnucobol
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[open-cobol-list] Bug in C$PARAMSIZE when PROGRAM-ID. xxx INITIAL.


From: Emilio Primi
Subject: [open-cobol-list] Bug in C$PARAMSIZE when PROGRAM-ID. xxx INITIAL.
Date: Thu, 28 Nov 2013 10:51:49 +0100

This bug appears in GNU-COBOL 2.0 from svn co 
svn://svn.code.sf.net/p/open-cobol/code/branches/gnu-cobol-2.0.

When the system function 'C$PARAMSIZE' is called from a program with the clause 
IINITIAL,
it returns the true length only on the first iteration, and returns zero on the 
others..

See the following TEST:

Main program:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TESTINITM.
      *--- TEST BEHAVIOR OF REITERATE CALL OF A SUBROUTINE
      *--- THAT USES INITIAL CLAUSE AND C$PARAMSIZE
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  PARAM1 PIC X(10) VALUE 'PARAM1'.
       01  PARAM2 PIC 9999 COMP VALUE 10.
       PROCEDURE DIVISION.
           PERFORM 10 TIMES
              CALL 'TESTINIT' USING PARAM1 PARAM2
           END-PERFORM.
           STOP RUN.

Called routine:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. TESTINIT. INITIAL.
      *-- SUBROUTINE TO BE CALLED MORE TIMES
      *-- BY A MAIN PROGRAMM
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01  COUNTER PIC 999 VALUE ZERO.
       01  LPARAM PIC 9(8) COMP.
       LINKAGE SECTION.
       01  PARAM1 PIC X.
       01  PARAM2 PIC 9999 COMP VALUE 10.
       PROCEDURE DIVISION USING PARAM1 PARAM2.
           ADD 1 TO COUNTER
           CALL 'C$PARAMSIZE' USING 1 GIVING LPARAM                             
                                          
           DISPLAY 'COUNTER = ' COUNTER ' LPARAM1 = ' LPARAM                    
                                          
           EXIT PROGRAM. 

The programs where compiled whith the option -m

Effect of cobcrun TESTINIT:

COUNTER = 001 LPARAM1 = 00000010
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000
COUNTER = 001 LPARAM1 = 00000000

If the clause INITIAL is removed, this is the result:

COUNTER = 001 LPARAM1 = 00000010
COUNTER = 002 LPARAM1 = 00000010
COUNTER = 003 LPARAM1 = 00000010
COUNTER = 004 LPARAM1 = 00000010
COUNTER = 005 LPARAM1 = 00000010
COUNTER = 006 LPARAM1 = 00000010
COUNTER = 007 LPARAM1 = 00000010
COUNTER = 008 LPARAM1 = 00000010
COUNTER = 009 LPARAM1 = 00000010
COUNTER = 010 LPARAM1 = 00000010

I hope this contribute for better evolution of a very good cobol implementation.

Emilio Primi
Cesip srl
Prato IT


reply via email to

[Prev in Thread] Current Thread [Next in Thread]