Re: ACCEPT or DISPLAY AT COL without LINE

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

 



2.0 was meant to be released at the start of the year. That didn't happen and I've got no idea what the current schedule is, sorry. If you ask on the Sourceforge forums, Simon or Brian might be able to fill you in.

On 21 May 2016 at 10:27, Dave Stratford <dave@xxxxxxxxxxxxxxx> wrote:
Is there any news on when the 2.0 branch will be formally released?

I'd like to try and convert some company code to run on the 2.0 branch,
but we have political problems:

I'm not allowed to put a cobol compiler on any of the company development
machines that isn't at 'production' status. Despite the cost of the
compiler licences we do use, our clients would rather pay out that money
than risk the possibility of problems caused by a compiler that itself is
still in development.

I have got it on my personal machine, but of course I'm not allowed to put
company code onto my personal machine.

Dave

Edward Hart wrote:
>> 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)
>
> That explains my failure to reproduce: this bug was fixed in the 2.0
> branch
> around February.
>
> I strongly recommend that you switch to the 2.0 branch. GnuCOBOL 1.1 was
> last updated in 2014 and I don't think it'll ever be updated. GnuCOBOL 2.0
> has
> a lot of bug fixes and it should have slightly better support for
> RM-COBOL.
>
> On 21 May 2016 at 04:54, David Newall <open-cobol@xxxxxxxxxxxxxxx> wrote:
>
>> 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
>


--
Dave Stratford      ZFCB
dave@xxxxxxxxxxxxxxx
Personal email address. Please do not pass on to anyone else.


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