gnucobol-users
[Top][All Lists]
Advanced

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

Re: [open-cobol-list] Problems with Display of multiple fields.


From: Chris Geldenhuis
Subject: Re: [open-cobol-list] Problems with Display of multiple fields.
Date: Tue, 01 May 2012 13:39:53 +0200
User-agent: Mozilla/5.0 (X11; Linux x86_64; rv:10.0.3) Gecko/20120314 Thunderbird/10.0.3

On 05/01/2012 10:42 AM, Fred Mobach wrote:
On Tuesday 01 May 2012 09:31:46 Chris Geldenhuis wrote:
Despite what is shown in Gary Cutler's excellent manual and used in
some of the examples in it, I cannot get a DISPLAY of multiple fields
to work.

Previously in MFC I would use:

DISPLAY identifier at POS, literal, identifier etc and would get all
identifiers and literals appearing on the screen one after the other.

When I compile this in Open Cobol only the first item in the list of
identifiers and literals appears on screen.

I have tried this with the "at POS" clause where shown above and at
the end of the statement as it appears to be required by the manual.

I have also tried using END-DISPLAY to terminate the DISPLAY
statements to no avail.
Perhaps the example below might help you. It was compiled with
   cobc -x<sourcefilename>
with openCOBOL v1.1 on a GNU/Linux system with openSUSE 12.1.

000010 IDENTIFICATION DIVISION.
000020 PROGRAM-ID. test0x.
000170 ENVIRONMENT DIVISION.
000180     COPY EDOBSR.
000190 DATA DIVISION.
000200 WORKING-STORAGE SECTION.
000210 01  W-REPLY                 PIC X(0001) VALUE SPACE.
000220 01  CURSORPOSITION          PIC 9(04).
000230 01  FORMSCOORDINATESTABLE.
000240     03  FILLER                 PIC X(06) VALUE "010204".
000250     03  FILLER                 PIC X(06) VALUE "034104".
000260     03  FILLER                 PIC X(06) VALUE "044101".
000270     03  FILLER                 PIC X(06) VALUE "054120".
000280     03  FILLER                 PIC X(06) VALUE "237504".
000290     03  FILLER                 PIC S9(03) COMP VALUE 005.
000300 01  FILLER REDEFINES FORMSCOORDINATESTABLE.
000310     03  FORMSFIELDS                  OCCURS 005.
000320         05  FORMSCOORDINATES   PIC 9(04).
000330         05  FORMSFIELDLENGTH   PIC 9(02).
000340     03  FORMSCOORD-MAX         PIC S9(03) COMP.
000350 01  LASTVIEWNAME.
000360     03  LASTSYSTEMREFERENCENAME PIC X(0004).
000370     03  LASTVIEWNR              PIC X(0003).
000380 01  CURRVIEWNAME    VALUE "MENS006".
000390     03  CURRSYSTEMREFERENCENAME PIC X(0004).
000400     03  CURRVIEWNR              PIC X(0003).
000420     COPY WSFORM.
000430     COPY CWS900.
000440 01  INPUT-AREA.
000450   02  INPUT-AREA-2.
000460         05  ESC-01-02 PIC X(04).
000470         05  ESC-03-41 PIC X(04).
000480         05  ESC-04-41 PIC X(01).
000490         05  ESC-05-41 PIC X(20).
000500         05  ESC-23-75 PIC X(04).
000510   02  OUTPUT-AREA-2.
000520         05  OSC-01-71 PIC X(02).
000530         05  OSC-01-74 PIC X(02).
000540         05  OSC-01-77 PIC X(02).
000550         05  OSC-04-48 PIC X(20).
000560         05  OSC-23-02 PIC X(72).
000570 SCREEN SECTION.
000580 01  FORMS-CONSTANTS-AREA AUTO.
000590     03  F-C-01.
000600         05  F-V-01-02 LINE 01 COL 02 PIC X(04)
000610             USING ESC-01-02 HIGHLIGHT UNDERLINE.
000620         05  F-C-01-27 LINE 01 COL 27  VALUE
000630                 "Country codes                         ".
000640         05  F-C-01-65 LINE 01 COL 65  VALUE "Date: ".
000650         05  F-V-01-71 LINE 01 COL 71 PIC X(02)
000660             FROM OSC-01-71.
000670         05  F-C-01-73 LINE 01 COL 73  VALUE "-".
000680         05  F-V-01-74 LINE 01 COL 74 PIC X(02)
000690             FROM OSC-01-74.
000700         05  F-C-01-76 LINE 01 COL 76  VALUE "-".
000710         05  F-V-01-77 LINE 01 COL 77 PIC X(02)
000720             FROM OSC-01-77.
000730     03  F-C-03.
000740         05  F-C-03-33 LINE 03 COL 33  VALUE "Country ".
000750         05  F-V-03-41 LINE 03 COL 41 PIC X(04)
000760             USING ESC-03-41 HIGHLIGHT UNDERLINE.
000770     03  F-C-04.
000780         05  F-C-04-32 LINE 04 COL 32  VALUE "Language ".
000790         05  F-V-04-41 LINE 04 COL 41 PIC X(01)
000800             USING ESC-04-41 HIGHLIGHT UNDERLINE.
000810         05  F-V-04-48 LINE 04 COL 48 PIC X(20)
000820             FROM OSC-04-48.
000830     03  F-C-05.
000840         05  F-C-05-28 LINE 05 COL 28  VALUE "Country name ".
000850         05  F-V-05-41 LINE 05 COL 41 PIC X(20)
000860             USING ESC-05-41 HIGHLIGHT UNDERLINE.
000870     03  F-C-23.
000880         05  F-V-23-02 LINE 23 COL 02 PIC X(72)
000890             FROM OSC-23-02.
000900         05  F-V-23-75 LINE 23 COL 75 PIC X(04)
000910             USING ESC-23-75 HIGHLIGHT UNDERLINE.
000920 PROCEDURE DIVISION
000960           .
000970 FIRST-SECTION SECTION.
000980 P00.
000990     MOVE 000SYSTEMREFERENCENAME TO LASTSYSTEMREFERENCENAME
001000     MOVE 000VIEWNR TO LASTVIEWNR
001010     IF X00FUNCTIONISBEEP = "N"
001020         DISPLAY SPACE UPON CRT
001030     ELSE
001040         DISPLAY SPACE UPON CRT
001050             WITH BEEP
001060         .
001070     DISPLAY FORMS-CONSTANTS-AREA
001080         AT 0101
001090     MOVE CURRVIEWNR TO 000VIEWNR
001100     IF 000FIELDCOUNT<  1 OR>  FORMSCOORD-MAX
001110         MOVE 1 TO 000FIELDCOUNT
001120         .
001130     MOVE FORMSCOORDINATES (000FIELDCOUNT) TO CURSORPOSITION
001140     ACCEPT FORMS-CONSTANTS-AREA
001150         AT 0101.
001160 PEOS. stop run.
Thanks for the response Fred,

I am not using the screen section to handle displays and accepts as the system being converted was originally written on a compiler where that was not available, and the conversion time frame does not allow me to change all of the accept and logic.

Regards

ChrisG



reply via email to

[Prev in Thread] Current Thread [Next in Thread]