Re: ACCEPT or DISPLAY AT COL without LINE

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

 



Hi Edward,

Here's two examples:

$ cat test-display-at.cbl
        IDENTIFICATION DIVISION.
        PROGRAM-ID.  "test-display-at".
        ENVIRONMENT DIVISION.
        CONFIGURATION SECTION.
        SOURCE-COMPUTER.  GNUCOBOL.
        OBJECT-COMPUTER.  GNUCOBOL.
        PROCEDURE DIVISION.
        MAIN-START.
            DISPLAY " Display at line 22,", AT LINE 22, POSITION 20.
            DISPLAY " position 20", AT POSITION 40.
            EXIT PROGRAM.
            STOP RUN.
        END PROGRAM "test-display-at".
$ cobc test-display-at.cbl
Unexpected tree tag 28
codegen.c:1304: Internal compiler error
Aborting compile of test-display-at.cbl at line 18
$ cat test-accept-at.cbl
        IDENTIFICATION DIVISION.
        PROGRAM-ID.  "test-accept-at".
        ENVIRONMENT DIVISION.
        CONFIGURATION SECTION.
        SOURCE-COMPUTER.  GNUCOBOL.
        OBJECT-COMPUTER.  GNUCOBOL.
        DATA DIVISION.
        WORKING-STORAGE SECTION.
        01  RETURN-KEY          PIC X.
        PROCEDURE DIVISION.
        MAIN-START.
            DISPLAY " Press Enter key to continue...",
                        AT LINE 22, POSITION 20.
            ACCEPT RETURN-KEY AT POSITION 55.
            EXIT PROGRAM.
            STOP RUN.
        END PROGRAM "test-accept-at".
$ cobc test-accept-at.cbl
Unexpected tree tag 28
codegen.c:1304: Internal compiler error
Aborting compile of test-accept-at.cbl at line 18

The compiler was compiled from source, using svn checkout 
svn://svn.code.sf.net/p/open-cobol/code/trunk open-cobol-code (and I 
just realised that is probably version 1.1, not 2.0), with plain 
./configure.  At the time it was revision 883.

David

------------------------------------------------------------------------------
Mobile security can be enabling, not merely restricting. Employees who
bring their own devices (BYOD) to work are irked by the imposition of MDM
restrictions. Mobile Device Manager Plus allows you to control only the
apps on BYO-devices by containerizing them, leaving personal data untouched!
https://ad.doubleclick.net/ddm/clk/304595813;131938128;j
_______________________________________________
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