VALUE clause in REDEFINE

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

 



Hi,

We are doing a port from a rather large software from AS400 and Microfocus to gnuCobol (2.0 rc1 on linux).

Most of the programs compile well, and most of the compilation errors can be corrected with a simple sed to accomodate with Cobol dialect differences, but we still have some programs that don't compile and for which I couldn't find an easy work around. 

Here is the most annoying one:

We have several programs here that have a VALUE in a REDEFINE clause.
eg:
       05 W-SEG-RFF.
                    10 FILLER            PIC X(05)  VALUE SPACES.
                    10 W-SEG-RFF-PAYEXT.
                       15 W-RFF-QUALIF-E    PIC X(02).
                       15 FILLER            PIC X(01)  VALUE SPACES.
                       15 W-RFF-REF-E       PIC X(12).
                       15 FILLER            PIC X(01)  VALUE SPACES.
                    10 W-SEG-RFF-PAYMUL REDEFINES W-SEG-RFF-PAYEXT.
                       15 W-RFF-QUALIF-M    PIC X(03).
>>>>>>                 15 FILLER            PIC X(01)  VALUE SPACES.
                       15 W-RFF-REF-M       PIC X(12).

Our 2 source compilers, Cobol 400 and Microfocus both raise a Warning and ignore the VALUE clause.

Gnu Cobol rejects this:
error: entries under REDEFINES cannot have a VALUE clause

I understand this is bad programming practice, but this code has beek working for years on legacy systems, so it would be really hard to convice our staff that this code is not correct. Despite the warnings.

Is there an option to tell gnuCobol to also ignore the VALUE clause?
Or should I open a feature request?
Or any other suggestion?


Regards,
Erwan
------------------------------------------------------------------------------
Check out the vibrant tech community on one of the world's most 
engaging tech sites, SlashDot.org! http://sdm.link/slashdot
_______________________________________________
open-cobol-list mailing list
open-cobol-list@xxxxxxxxxxxxxxxxxxxxx
https://lists.sourceforge.net/lists/listinfo/open-cobol-list

[Index of Archives]     [Gcc Help]     [Linux USB Devel]     [Linux Audio Users]     [Yosemite Info]     [Linux Kernel]     [Linux SCSI]     [Big List of Linux Books]

  Powered by Linux