Þaw
Þaw

Reputation: 2057

Trouble with ACCEPT "ESC-CODE FROM ESCAPE KEY"

With Microsoft COBOL Compiler version 2.2 and I have this code that completely worked fine.

   IDENTIFICATION DIVISION.
   PROGRAM-ID. COCENTRY.
   ENVIRONMENT DIVISION.
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.
       SELECT COC-FILE
         ASSIGN TO DISK
         ORGANIZATION IS INDEXED
         ACCESS MODE IS RANDOM
         RECORD KEY IS COCNO
           FILE STATUS IS FILE-STATUS.
   DATA DIVISION.
   FILE SECTION.
   FD  COC-FILE LABEL RECORD IS STANDARD
       VALUE OF FILE-ID IS "COC.DAT".
   01  COC-RECORD.
       03  COCNO            PIC 9(5).
       03  COCDESC          PIC X(40).
   WORKING-STORAGE SECTION.
   01  FILE-STATUS  PIC XX.
   01  ESC-CODE PIC 99 VALUE 0.
       88  ESC-KEY  VALUE 1.
       88  F2       VALUE 3.
       88  F10      VALUE 11.
   01  ERRMSG       PIC X(70) VALUE SPACES.
   01  ERR          PIC 9 VALUE 0.
   SCREEN SECTION.
   01  FORM1.
       03 BLANK SCREEN BACKGROUND-COLOR 1.
       03 LINE 1 COLUMN 1 'COCNO'.
       03 LINE 2 COLUMN 1 'COCDESC'.
       03 LINE 24 COLUMN 1 "Esc=Exit  F2=Save  F10=Cancel".
       03 LINE 25 COLUMN 1 PIC X(70) FROM ERRMSG HIGHLIGHT.
   01  FORM2.
       03 LINE 1 COLUMN 14 PIC 9(5)
          USING COCNO REVERSE-VIDEO.
       03 LINE 2 COLUMN 14 PIC X(40)
          USING COCDESC REVERSE-VIDEO.
       03 LINE 24 COLUMN 1 PIC 99
          USING ESC-CODE.
   PROCEDURE DIVISION.
   MAIN.
       OPEN I-O COC-FILE.
       IF FILE-STATUS NOT = '00'
           OPEN OUTPUT COC-FILE
           CLOSE COC-FILE
           OPEN I-O COC-FILE.
       PERFORM ENTRY1 THRU ENTRYX UNTIL ESC-KEY.
       CLOSE COC-FILE.
       STOP RUN.
   ENTRY1.
       MOVE SPACES TO COC-RECORD.
       MOVE ZEROES TO COCNO.
   ENTRY2.
       DISPLAY FORM1 FORM2.
       ACCEPT FORM2.
       ACCEPT ESC-CODE FROM ESCAPE KEY.
       IF F10
           MOVE 'Entries canceled...' TO ERRMSG
           GO ENTRY1
       ELSE IF F2
           GO ENTRY3
       ELSE IF ESC-KEY
           GO ENTRYX
       ELSE
           GO ENTRY2.
   ENTRY3.
       MOVE 0 TO ERR.
       WRITE COC-RECORD INVALID KEY MOVE 1 TO ERR.
       IF ERR = 1
           MOVE 'Duplicate key not allowed...' TO ERRMSG
           GO ENTRY2
       ELSE
           MOVE 'Entries recorded...' TO ERRMSG
           GO ENTRY1.
   ENTRYX.
       EXIT.

Now I am using OpenCobol IDE 4.3.0 having GNUCobol version 1.1.0 and I am being prompted with this lines of

syntax error, unexpected "Literal", expecting LEADING or TRAILING

 03 LINE 1 COLUMN 1 'COCNO'.
 03 LINE 2 COLUMN 1 'COCDESC'.
 03 LINE 24 COLUMN 1 "Esc=Exit  F2=Save  F10=Cancel".

So I fix them by adding VALUE keyword:

 03 LINE 1 COLUMN 1 VALUE 'COCNO'.
 03 LINE 2 COLUMN 1 VALUE 'COCDESC'.
 03 LINE 24 COLUMN 1 VALUE "Esc=Exit  F2=Save  F10=Cancel".

but as soon as I do this I get a another prompt of

'ACCEPT .. FROM ESCAPE KEY' not implemented

on this line

ACCEPT ESC-CODE FROM ESCAPE KEY.

What could be the possible cause of this? And what could be the fix for this?

Upvotes: 2

Views: 2069

Answers (3)

Luis
Luis

Reputation: 1

PROCEDURE DIVISION.
           SET ENVIRONMENT 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
           SET ENVIRONMENT 'COB_SCREEN_ESC'        TO 'Y'.
  • Escape: IF cob-crt-status = 2005......
  • Enter: IF cob-crt-status = 0........
  • F1: IF cob-crt-status = 1001......
  • F2: IF cob-crt-status = 1002......

Upvotes: 0

Bill Woodger
Bill Woodger

Reputation: 13076

Your actual answer is here, https://sourceforge.net/p/open-cobol/discussion/help/thread/26a01c5f/, on the GnuCOBOL part of SourceForge. With minor changes your code will "completely work" with the change you've already made to include the VALUE clause, and if you use release 2.0 or higher of the GnuCOBOL compiler.

Your code may "completely work" but it is spaghetti code.

The term comes from the old days, and relates to the use of many branches in programs, a common practice at that time, but which made trying to follow the logic a process like trying to follow one strand of cooked spaghetti which is part of a pile of cooked spaghetti.

If you change this:

PERFORM ENTRY1 THRU ENTRYX UNTIL ESC-KEY.

To this:

PERFORM ENTRY1 THRU ENTRYX.

Your program will still work. Confused? Yes, because you have spaghetti. Your program flow will only ever get to ENTRYX once. The value when it arrives at ENTRYX is ESC-KEY, but that is superfluous, because it can only ever get there once, when it is ESC-KEY. Clear? No? Because you have spaghetti.

Here is your logic, re-written:

   PROCEDURE DIVISION.
       OPEN I-O COC-FILE
       IF FILE-STATUS NOT = '00'
           [the following code is a horror. Deal with this outside the 
           program. Crash for an unexpected FILE STATUS on OPEN]
           OPEN OUTPUT COC-FILE
           CLOSE COC-FILE
           OPEN I-O COC-FILE
       END-IF
       PERFORM PROCESS-USER-INPUT
         UNTIL ESC-KEY
       CLOSE COC-FILE
       IF FILE-STATUS NOT = '00'
           [something bad has happened, so don't go quietly]
       END-IF
       GOBACK
       .
   PROCESS-USER-INPUT.
       PERFORM BLANK-OUTPUT-RECORD
       PERFORM PROCESS-COC
         UNTIL ESC-KEY
       .
   PROCESS-COC.

       DISPLAY FORM1 FORM2
       ACCEPT FORM2
       ACCEPT ESC-CODE FROM ESCAPE KEY
       EVALUATE TRUE
         WHEN F10
           MOVE 'Entries canceled...' TO ERRMSG
         WHEN F2
           PERFORM CREATE-OUTPUT
       END-EVALUATE
       .
   CREATE-OUTPUT.
       WRITE COC-RECORD 
       IF ATTEMPT-TO-WRITE-DUPLICATE [22 on the FILE STATUS field]
           MOVE 'Duplicate key not allowed...' TO ERRMSG
       ELSE
           MOVE 'Entries recorded...' TO ERRMSG
           PERFORM BLANK-OUTPUT-RECORD
       END-IF
       .
   BLANK-OUTPUT-RECORD.
       MOVE SPACES TO COC-RECORD
       MOVE ZEROES TO COCNO
       .

Does that make your program look simpler? Easier to follow, change, understand what it does when someone else looks at it (or when you do in two weeks time)?

There are other things, like why set COC-RECORD to space, and then COCNO to zero? Move the spaces to COCDESC.

Make your data/procedure names good and descriptive. FILE STATUS having a good name (don't call it FILE-STATUS) and one per file when you have more than one file. Use full-stops/periods only where you have to, and use scope-delimiters for all conditional constructs that you use. Use FILE STATUS checking for all IO, and don't use the tortuous AT on IO.

If you look now the first code in your program is quite long, executes only once, and is (should be) irrelevant to the business function of your program. So stick all that in a paragraph, and PERFORM that. Same for the close. Then you can have as much code as you need when starting up and closing down, without making your program more difficult to follow.

Upvotes: 4

Joe Zitzelberger
Joe Zitzelberger

Reputation: 4263

The screen and keyboard I/O was a MicroSoft Cobol specific flavor. You will likely need to tweak that a bit to make it work with OpenCobol.

Upvotes: 3

Related Questions