Re: PIC 1

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

 




Am 30.07.2021 um 06:03 schrieb Michael Potter:
Gnu Crew,

I am compiling some COBOL that I got from an AS/400.

           05  FILE-FLAG   PIC 1    VALUE B"0".
                 88 FILE-FLAG-OPEN   VALUE B"1".
                 88 FILE-FLAG-CLOSE  VALUE B"0".


I am not the most widely travelled man, but I have never seen a PIC 1
before.  The context appears to be a boolean.

Totally correct. This became standard COBOL with COBOL2002

The GnuCOBOL 3.1 RC-1 programmer's guide does not reference PIC 1 (as
far as I can see by quick search of syntax of PICTURE-STRING).

It throws this error:

AXXXXA.cbl: 146: error: invalid PICTURE character '1'

AXXXXA.cbl: 146: error: PICTURE string must contain at least one of the
set A, N, X, Z, 1, 9 and *; or at least two of the set +, - and the
currency symbol


Which is curious because the error message refers to 1 as a valid
character in the picture clause.


That's because it is not implemented yet but the syntax check for the
PICTURE characters were written against the standard already.

1. How can I get this code to compile and run?

a) explicit change PIC 1 to PIC 9
b) as GnuCOBOL 2.x got (a likely unfinished implementation of) that in
2018 (see the related FR [1]) - double check your version; there has to
be a really big reason to use anything older than 2.2 (and also using
2.2 would be a bit questionable)

2. How could have I found that answer myself?

In general I'd suggest to have a look at the COBOL standard first, when
inspecting "what is that" (there is a public draft available for
whatever COBOL standard is in the progress [2]). In this case you'd have
found:

13.18.39.3 DATA DIVISION clauses, PICTURE clause, General rules
> 1  Each symbol '1' represents a boolean position that will be checked
to contain a boolean character.

To find out about potential bugs and feature requests: check the issue
trackers [3].

To find out what GnuCOBOL does: check the source, for parsing and
general syntax checks in cobc/parser.y, cobc/typeck.c and cobc/tree.c.

3. If I have to change code what is the easiest thing to do?  I have a
couple hundred I would need to change.

For changing the sources I'd go with something like (warning: GNU
extension):

	sed -i -e 's/\(\s\(pic\|picture\)\s\+1\)/\2 9/gi'


But a quick test shows that GC 3.1.2 at least compiles a test source
with that (likely without bailing out when using -std=cobol85); if you
see something else then please provide a minimal example.

Note: Without a deep check I _think_ boolean items are unfinished, they
should work with direct MOVE and conditionals but use more than a single
bit in storage - so programs that interoperate with non-gnucobol modules
should not pass PIC 1 items via CALL/PROCEDURE DIVISION USING.

Simon

[1] https://sourceforge.net/p/gnucobol/feature-requests/303/
[2] https://isotc.iso.org/livelink/livelink?func=ll&objId=19468956
[3] https://sourceforge.net/p/gnucobol/_list/tickets





[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