Re: VALUE clause in REDEFINE

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

 



Ok, I'll try the reportwriter branch, though I'm not interested in the mF date files options, as we use Oracle OCI wrappers written in C to access our data. 
Hope there are not too many differences for me between reportwriter and 2.0.

BTW, I do alse have a "error: REDEFINES must follow the original definition" problem.
Do you think reportwriter might help too?

Erwan


2016-10-03 23:02 GMT+02:00 Ron Norman <rjn@xxxxxxxxxxxx>:
I just checked the 2.0 source code and you are correct. 
I work mostly with the reportwriter branch.

The reportwriter branch of the compiler does handle this condition as a warning when -frelax-syntax is used.

At some point the reportwriter branch is to get merged into 2.0 but I am not sure when that will happen...

The reportwriter branch also has options to support Micro Focus format data files for sequential and direct which may make moving from MF to GNUCobol easier...


On Mon, Oct 3, 2016 at 4:50 PM, Erwan Duroselle <erwan.duroselle@xxxxxxxxx> wrote:
Thanks for the tip, but I still have an error with -frelax-syntax.






2016-10-03 22:37 GMT+02:00 Ron Norman <rjn@xxxxxxxxxxxx>:
Use the compile option -frelax-syntax for cobc and then that error should reduce to a warning.

On Mon, Oct 3, 2016 at 4:19 PM, Erwan Duroselle <erwan.duroselle@xxxxxxxxx> wrote:
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@lists.sourceforge.net
https://lists.sourceforge.net/lists/listinfo/open-cobol-list




--
Cheers
Ron Norman




--
Cheers
Ron Norman

------------------------------------------------------------------------------
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