code folding for COBOL

This forum should be used for all code folding problems, questions or suggestions. You can also use this forum to request folding support for a new language.
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

I didn't see a request for code folding for COBOL and since I don't see any folding going on in my .COB files, I'll assume it hasn't been implemented.

A word about matching pairs of begin/end fold keywords: Commands like 'IF' can be terminated with the matching end keyword (i.e. 'END-IF') or by a period ('.'). Since there is no line continuation character, a command like 'DISPLAY' which has no matching end keyword can span multiple lines and, if possible, should be folded when it does.

Local variables are declared in the 'WORKING-STORAGE SECTION' and are defined using 'level numbers' (e.g. 01, 02, etc.). Lines that contain these level numbers should be folded to the next line containing a level number of the same value (unless the next level number is greater than the current level number).

Since COBOL is column sensitive, any line that contains either of the words 'DIVISION' or 'SECTION', can be folded to the next line that begins in column 8 and contains either of the words 'DIVISION' or 'SECTION' (respectively). Any line that begins in column 8 and does NOT contain either of the words 'DIVISION' or 'SECTION' can be folded to the next line that begins in column 8 and does NOT contain either of the words 'DIVISION' or 'SECTION'.

Extension: .COB
Line Comment: * (column 7 only)
Block Comment: none

Begin: IF
End: END-IF (or '.')
Begin: PERFORM
End: END-PERFORM (or '.')
Begin: EVALUATE
End: END-EVALUATE (or '.')

Sample Code:

Code: Select all

       IDENTIFICATION DIVISION.
       PROGRAM-ID. PD254C.
       *-------------------------------------------
       *-------------------------------------------
       ENVIRONMENT DIVISION.
       CONFIGURATION SECTION.
       SOURCE-COMPUTER. IBM-PC.
       OBJECT-COMPUTER. IBM-PC.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
       FILE SECTION.
       *-------------------------------------------
       WORKING-STORAGE SECTION.
       01  NUMBER-OF-PARAMETERS    PIC 99 COMP-1.
       *-------------------------------------------
       COPY "BTRLIB.COB".
       COPY "RCI711LB.COB".
       COPY "RCI800LB.COB".
       COPY "RCI598LB.COB".
       COPY "PD700HLP.COB".
       COPY "PD520LIB.COB".
       *-------------------------------------------
       01  WORK-AREA.
           02 PROJECT-NO-WS        PIC X(200).
       01  KI-AREA.
           02 PROJECT-NAME-KI      PIC X(30).
       *-------------------------------------------
       LINKAGE SECTION.
       01 PROJECT-NO-PARAM         USAGE HANDLE.
       *-------------------------------------------
       PROCEDURE DIVISION USING PROJECT-NO-PARAM.
       *-------------------------------------------
       MAIN-LINE.
           CALL 'C$NARG' USING NUMBER-OF-PARAMETERS.
           IF NUMBER-OF-PARAMETERS < 1
               GO TO EOJ
           END-IF.

           CALL 'C$GETVARIANT' USING PROJECT-NO-PARAM,
                               PROJECT-NO-WS.

           CALL 'PD253.CBX' USING PROJECT-NO-WS.
           CALL 'PD253.CBX'.
           CANCEL 'PD253.CBX'.

       EOJ.
           GOBACK.
       *-------------------------------------------
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Hi Jon,

Thank you for posting the Cobol folding definition. Check back in a few days to see how it has progressed ;)
Line Comment: * (column 7 only)
As a side note the current Zeus Cobol Document Type needs to be modified to reflect this point.

Currently the Keywords section of the Cobol Document Type defines a line comment as * but this should be be changed to read 7:*.

That will mean something like this line of text is painted as a comment:

Code: Select all

1234567890 < these are column number only
      *-------------------------------------------
where as these two lines of text will not bee seen as a comment:

Code: Select all

1234567890 < these are column number only
     *-------------------------------------------
       *-------------------------------------------
Cheers Jussi
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Hi Jon,

The good news is the SECTION and DIVISION folding seems to work fine :)

But unfortunately there does seem to be an issue with the IF, PERFORM and . code folding caseS :(

For example consider this COBOL code that will fold correctly:

Code: Select all

+  IF (NW-WORK-CHAR(NW-WX) = "-")
-     SET NW-WX UP BY 1.
Next consider the following code that will not fold correctly due to the . at the end of the line:

Code: Select all

-  MOVE SPACES TO NW-WORK-NBR.
The + and - characters indicate the fold points found.

In the second case Zeus marks the line as an end of fold because it will detect the . found at the end of this line. But in the context of the code this is in fact not a fold :(

The problem is the Zeus folder is fairly primitive in that it assumes for every start of fold there is a matching end of fold.

Also the fold state of any given line is determined solely by the line itself. The lines before or after the line play no part in determining the fold state of that line.

For the folding to work I will need to know every valid COBOL keyword that can start a line and end with the . character.

Cheers Jussi
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

Great to hear about the progress on the COBOL code folding.

I have modified my COBOL document type for the comment character.

Here is a list of COBOL keywords that can start a line and end with the . character (there may be some I've missed):

ACCEPT
ACQUIRE
ADD
ALTER
CALL
CANCEL
CLOSE
COMMIT
COMPUTE
DELETE
DISPLAY
DIVIDE
DROP
EXIT
EXIT PROGRAM
GO TO
GOBACK
INITIALIZE
INSPECT
MERGE
MOVE
MULTIPLY
OPEN
PERFORM
READ
RELEASE
RETURN
REWRITE
ROLLBACK
SET
SORT
START
STOP
STOP RUN
STRING
SUBTRACT
UNSTRING
WRITE

Some of these statements also have an implicit terminator so I've also included them here:

END-ACCEPT
END-ADD
END-CALL
END-COMPUTE
END-DELETE
END-DIVIDE
END-EVALUATE
END-IF
END-MULTIPLY
END-PERFORM
END-READ
END-RETURN
END-REWRITE
END-SEARCH
END-START
END-STRING
END-SUBTRACT
END-UNSTRING
END-WRITE

Thanks for providing great support for a great product!
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

The COBOL code folding changes have been made and the new xFolder.dll can be found here:

http://www.zeusedit.com/z300/xFolder.zip

To install this new dll backup the current dll and replace it with the one contained in the zip file.

To complete the install you will need to create a WinBatch document type and enable the code folding option.

The new xFolder.dll file does COBOL code folding based on the indent levels of the code. Here is some typical COBOL code that illustrates what I mean by indent levels:

Code: Select all

           PERFORM 000100-PROCESS
              THRU 000100-EXIT
               UNTIL (WS-ESCAPE-FLAG = 1).

           PERFORM 003000-GET-NBR
              THRU 003000-EXIT.

           IF (NW-NBR-ERROR-FLAG = 1)
               MOVE "NUMBER INVALID" TO WS-ERR-MSG
           ELSE
               MOVE SPACES           TO WS-ERR-MSG.
I am not sure how well indent level folding this is going to work well for COBOL, so feel free to post any comments, suggestions or bug reports to the end of this thread.

Cheers Jussi
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

Zeus rules! We've just finished our evaluation and bought licenses for the entire office. COBOL code folding would be very well received here.

I downloaded the xFolder dll and checked it out on our COBOL files:

A few observations/comments:

Lines that begin in column 8 and have the word DIVISION are wrapping to the next line that begins in column 8 and has the word SECTION. This is not correct. A DIVISION contains SECTIONs so the DIVISION line should fold to the next DIVISION line. A SECTION line should fold to the next SECTION line with that DIVISION or to the next DIVISION line (if it is the last SECTION in that DIVISION).

In the WORKING-STORAGE SECTION, the level numbers are heirarchial can be folded based on level number. A level 01 variable can encapsulate level 02 variables which in turn can encapsulate level 03 variables, etc., etc. Following this heirarchy, level 01 can fold to the next level 01. A level 02 can fold to the next level 02 within that level 01. A level 03 can fold to the next level 03 within that level 02. Another way to say it is that a level number can fold to the next level number less than or equal to itself.

Lastly, the folding based on indent levels does not work well so I would suggest throwing that away and just use the following explicit begin and end terms:

Begin: ACCEPT
End: END-ACCEPT
Begin: ADD
End: END-ADD
Begin: CALL
End: END-CALL
Begin: COMPUTE
End: END-COMPUTE
Begin: DELETE
End: END-DELETE
Begin: DIVIDE
End: END-DIVIDE
Begin: EVALUATE
End: END-EVALUATE
Begin: IF
End: END-IF
Begin: MULTIPLY
End: END-MULTIPLY
Begin: PERFORM
End: END-PERFORM
Begin: READ
End: END-READ
Begin: RETURN
End: END-RETURN
Begin: REWRITE
End: END-REWRITE
Begin: SEARCH
End: END-SEARCH
Begin: START
End: END-START
Begin: STRING
End: END-STRING
Begin: SUBTRACT
End: END-SUBTRACT
Begin: UNSTRING
End: END-UNSTRING
Begin: WRITE
End: END-WRITE


Thanks for such a great product and for providing outstanding support!
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Hi Jon,
Zeus rules! We've just finished our evaluation and bought licenses for the entire office.
Thank you for supporting the ongoing Zeus development with your registration :)
A DIVISION contains SECTIONs so the DIVISION line should fold to the next DIVISION line.
Unfortunately the current folder is not smart enough to achieve this sort of folding logic :(

The current folder only sees begin/end fold points and has no way of associating additional information with these points.

So for the mean time what do you think would be the be the best partial fix to this problem: :?:
  1. Leave it as it is
  2. Fold on SECTIONs but not DIVISIONs
  3. Fold on DIVISIONs but not SECTIONs
  4. Remove the DIVISIONs, SECTIONs folding
  5. Change the DIVISIONs, SECTIONs folding to work like the IF and use indent level
I will also take some time to think about making the folder a little smarter ;)
Following this heirarchy, level 01 can fold to the next level 01.

Could you post a small snippet of code that shows this heirarchy.
Lastly, the folding based on indent levels does not work well so I would suggest throwing that away and just use the following explicit begin and end terms:
A new xFolder.dll is now available that supports these extra fold points. Just download it from the same link mentioned earlier.

It will most probably require some fine tuning so let me know if it works any better ;)

Cheers Jussi
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

Hi Jussi,

Thanks for taking suggestions on this and for your efforts in making Zeus even more useful for our staff.
The current folder only sees begin/end fold points and has no way of associating additional information with these points.

So for the mean time what do you think would be the be the best partial fix to this problem:

1. Leave it as it is
2. Fold on SECTIONs but not DIVISIONs
3. Fold on DIVISIONs but not SECTIONs
4. Remove the DIVISIONs, SECTIONs folding
5. Change the DIVISIONs, SECTIONs folding to work like the IF and use indent level
I would choose #2, 'Fold on SECTIONs but not DIVISIONs.
Could you post a small snippet of code that shows this heirarchy.

Code: Select all

       01  WS-AREA.
           02 HOLD-4                 PIC 9999.
           02 LIST-SIZE              PIC 9999.
           02 LINE-NO                PIC 9999.
           02 NUM-PARAM              PIC 9 COMP-1.

       01  LINK-NA100.
           02 LINK-NA111.
              03 ALT-KEY-LINK.
                 04 TABLE-LINK       PIC 9999.
                 04 ENTRY-LINK       PIC 9999.
                 04 FIELD-1-LINK     PIC X(20).
                 04 FIELD-2-LINK     PIC X(20).
                 04 FIELD-3-LINK     PIC X(20).
                 04 FIELD-4-LINK     PIC X(20).
                 04 NUMBER-LINK      PIC 9(9).
           02 SWITCH-LINK VALUE 1    PIC 9.
           02 LINK-NA112.
              03 ALT12-KEY-LINK.
                 11 TABLE12-LINK     PIC 9999.
                 11 ENTRY12-LINK     PIC 9999.
                 11 FIELD12-1-LINK   PIC X(20).
                 11 FIELD12-2-LINK   PIC X(20).
                 11 FIELD12-3-LINK   PIC X(20).
                 11 FIELD12-4-LINK   PIC X(20).
                 11 NUMBER12-LINK    PIC 9(9).

       01  LIST-LINE.
           02 SYSTEM-KI              PIC XX.
           02 VENDOR-NO-KI           PIC ZZZZZZZZ9.
           02 VENDOR-NAME-KI         PIC X(20).
           02 AMOUNT-KI              PIC --,---,---.99.
           02 DATE-KI                PIC X(10).
           02 TRANSACTION-TYPE-KI    PIC ZZZ9.
           02 TRANSACTION-NAME-KI    PIC X(20).
           02 HS-544-KI              PIC X(250).

       01  RETURN-FLAG-LINK          PIC 9.

       01  PASS-LINK                 PIC 9.
           88 INITIALIZE-PASS VALUE 1.
           88 ADD-ITEM-PASS   VALUE 2.
           88 PREVIEW-PASS    VALUE 3.
           88 CREATE-PASS     VALUE 4.
Please bear in mind that the level number heirarchy is not required to follow strict increments (i.e. 01 then 02 then 03). The heirarchy is only required to begin at level 01 and any 'child' levels must have a level number that is greater than the 'parent' level.

Please let me know if this is sufficient.

Thanks again for all your efforts.

Jon
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Hi Jon,
I would choose #2, 'Fold on SECTIONs but not DIVISIONs.

A new xFolder.dll that implements this change will be posted shortly ;)
The heirarchy is only required to begin at level 01 and any 'child' levels must have a level number that is greater than the 'parent' level.

Doesn't the current xFolder.dll already handle this type of code folding :?:

For example with the following COBOL code as an example:

Code: Select all

-      01  WS-AREA. 
-           02 HOLD-4                 PIC 9999. 
-           02 LIST-SIZE              PIC 9999. 
-               03 LINE-NO                PIC 9999.

This can be folded to this:

Code: Select all

+      01  WS-AREA.

or this:

Code: Select all

-      01  WS-AREA. 
-           02 HOLD-4                 PIC 9999. 
+           02 LIST-SIZE              PIC 9999.

or this:

Code: Select all

-      01  WS-AREA. 
+           02 HOLD-4                 PIC 9999. 
+           02 LIST-SIZE              PIC 9999.

or this:

Code: Select all

-      01  WS-AREA. 
+           02 HOLD-4                 PIC 9999. 
-           02 LIST-SIZE              PIC 9999. 
-               03 LINE-NO                PIC 9999.

Granted these last two folds do look a little strange since this line of code:

Code: Select all

-           02 HOLD-4                 PIC 9999.

is folded to this:

Code: Select all

+           02 HOLD-4                 PIC 9999.

But the node has been folded correctly since the line contained no children.

Cheers Jussi.
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

Quote:
I would choose #2, 'Fold on SECTIONs but not DIVISIONs.

A new xFolder.dll that implements this change will be posted shortly.
Fantastic!
Quote:
The heirarchy is only required to begin at level 01 and any 'child' levels must have a level number that is greater than the 'parent' level.

Doesn't the current xFolder.dll already handle this type of code folding?
My xFolder.dll folds correctly if the code indentation is spot-on but if there is any deviation (an extra or a missing space), the folding doesn't work correctly and can be confusing.

Hope this helps.

Jon
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

The latest Zeus patch found here: http://www.zeusedit.com/forum/viewtopic.php?t=570

will fix these COBOL folding issues ;)

Cheers Jussi
JonShrout
Posts: 11
Joined: Mon May 01, 2006 10:50 pm

code folding for COBOL

Post by JonShrout »

Jussi,

Thanks for the update! The code folding for COBOL works better but there are still some issues. If you want to pursue it further, I'm happy to post with issues I find.

Currently the folding based on indentation does not work well. It gives unexpected results (e.g. verbs fold to the end of the file).

Thanks again for your hard work on this great product.

Jon
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Hi Jon,
The code folding for COBOL works better but there are still some issues. If you want to pursue it further, I'm happy to post with issues I find.
Any feedback would be great. Making changes to the xFolder.dll is not very difficult, but knowing which changes to make is only possible with feedback from people like yourself :)

Fell free to post as many comments, problems or suggestions you might have to this thread.
Currently the folding based on indentation does not work well. It gives unexpected results (e.g. verbs fold to the end of the file).
If you could post a minimal code sample (ie 4 or 5 lines of code) that illustrates this or any other error, that would be great.

The folder is only based on a very small subset of COBOL code and more likely than not unusual coding construct are not be represented in this subset of COBOL code :(

For this reason feel free to post as many code samples as you can think of as these will get added to this subset for testing. If you use the code button found on the reply page, it is possible to maintain the code structure in the reply.

Cheers Jussi
jussij
Site Admin
Posts: 2650
Joined: Fri Aug 13, 2004 5:10 pm

Post by jussij »

Unfortunately the xFolder.dll that came with the latest patch does not do the COBOL end of fold case correctly :(

To fix this issue please download a replacement xFolder.dll from the link shown earlier in this thread.

Cheers Jussi
pwdiener
Posts: 134
Joined: Wed Jul 11, 2007 3:45 pm

Some new bug reports and requests

Post by pwdiener »

COBOL Code Issues/Requests

Jussi,

I've sent you by private email a program that illustrates the issues and
requests below. The program is copyrighted by my employer, so I can't
just post it publicly.

Issues:
1) Line 1315 shows a fold for no apparent reason. This is a minor issue.
Line 1329 is similar, and there are many others. Line 1337 is an example
of a reasonable fold in similar circumstances as line 1329.

2) Comments seem to confuse the folder. For example, line 1432 is fine,
while just above it line 1428 does not show a fold. See also the fold at
line 1593 that includes the code at 1598 instead of making it a separate
fold.

3) Multiple lines seems to confuse the folder. For example, line 1522
shows a fold point, but only 1 line instead of the many (down to 1550)
that I would expect based on indentation or level numbers. Line 2650 is
another example - there I would expect a fold down to 2832.

4) In the procedure division, each time a verb is used that has a
corresponding END- form (e.g. PERFORM/END-PERFORM, ACCEPT/END-ACCEPT, etc.), the fold extends to the end of the program if the END- terminator is not present. For an example, see line 4275. Use of the END- terminator is not required, and in older programs is uncommon. Even newer programs tend not to use them when not needed, with the possible exception of END-IF. In all of these cases, a period will serve as a terminator of all previously unterminated statements (e.g. line 5177 thru 5184.
Immediately below line 4275 are several more examples. The folder appears to work properly when the END- terminator is present, for example line 4290 with IF/ELSE/END-IF is fine. Line 4344, however, without an END-IF, folds the ELSE clause to the end of the program.

5) Again, folds are shown for no apparent reason. e.g. line 4323.

Requests
1) The ability to turn off cetain types of folding. For instance, I think
the statement folding in the PROCEDURE DIVISION will be very difficult to
get right without a syntax analysis. While this doesn't destroy the
usefulness of folding, it makes it questionable. It would be very useful
to have a working folder that is syntax-directed, but it seems pretty
costly too.

2) The ability to fold contiguous comments. As an example see the large
comment block at the beginning. Lines 4-1151 could be folded.

3) The ability to fold paragraphs, particularly in the PROCEDURE DIVISION. If I had to choose, I'd say paragraphs instead of SECTIONs or DIVISIONs would be the better choice. Outside of the PROCEDURE DIVISION, paragraphs and sections have fixed names, but inside the paragraphs or sections can have any name. A paragraph name is a single word beginning in Area A (cols 8-11) ending with a period, while a section is a word beginning in Area A followed by the word SECTION and a period. Pardon me if I'm telling you things you already know.

Of these, request #3 would be the most useful to me.

A project that I've set myself will involve building a syntax-directed parser for COBOL. I don't have any idea when I'm going to get there, but when I do, it would be nice to leverage that to address folding issue #4. Any information you can share regarding interfaces you might need would be helpful in planning this.

Thanks.
Post Reply