Hi Michael, the current EBCDIC support in GnuCOBOL is limited to: * `make checkall` (internal and NIST85 tests) pass when running on an "EBCDIC native" environment * understands EBCDIC numeric display sign when interpreted, to use it for "creating" them on an "ASCII native" you can compile with -fsign=ebcdic * you can specify "IS EBCDIC" for an ALPHABET in special names and so do stuff like referenced currently in the FAQ under 5.16 [1]: SPECIAL-NAMES. ALPHABET ALPHA IS NATIVE. ALPHABET BETA IS EBCDIC. PROCEDURE DIVISION. INSPECT variable CONVERTING ALPHA TO BETA * you can reference an EBCDIC alphabet to be used as collation for `SORT table`: SORT TBL DESCENDING KEY X SEQUENCE BETA [1]: https://gnucobol.sourceforge.io/faq/index.html#ebcdic As far as I know from the discussion boards there are EBCDIC preparsers, but GnuCOBOL has not yet build-in support for EBCDIC as needed, which at least would be: * allow EBCDIC encoded source-code (converted to ASCII on read-in) --> work around: one-time change with iconv * an option to change the "NATIVE" collation to EBCDIC by dialect option * an option to change the PROGRAM COLLATING SEQUENCE by command-line option * allow to specify the collation for ORGANIZATION INDEXED (it is always "native" with the exclusion of DB collections setup externally with the DB INDEXED handlers in GnuCOBOL 4) * on-the-fly conversion of ACCEPT/DISPLAY, possibly also for parameters in LINKAGE/CALL USING That's all definitely on the road-map - but so far only as "patches welcome". Simon BTW: and of course "EBCDIC" itself also comes with different variants, GnuCOBOL EBCDIC alphabet, if unpatched, is likely the "default US variant" Am 18.05.2021 um 18:40 schrieb Michael Potter:
Hi All, I see that GnuCOBOL supports EBCDIC based on section 5.48 of the FAQ. Is anyone using it rigorously in production that I can trust it is well tested? Are there any caveats to using it that I should be aware of? For instance, how might it be different than the MicroFocus support for EBCDIC? I have used the MicroFocus support for EBCDIC for many years without any issues. I am hoping that GnuCOBOL works the same. Also, how do I specify that a COBOL program is to be compiled with EBCDIC support? The context of that question is I don't see a compile option here: https://manpages.debian.org/testing/gnucobol/cobc.1.en.html <https://manpages.debian.org/testing/gnucobol/cobc.1.en.html>