Skip to content

Commit 3de10c7

Browse files
authored
Improve COBOL snippets
Fix syntax errors in COBOL snippets Improve loop readability in COBOL snippets Signed-off-by: Janos Varga <113785741+vargajb@users.noreply.github.com>
1 parent 46d3a5c commit 3de10c7

File tree

1 file changed

+26
-24
lines changed

1 file changed

+26
-24
lines changed

COBOL Programming Course #2 - Learning COBOL/COBOL Programming Course #2 - Learning COBOL.md

Lines changed: 26 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1091,7 +1091,7 @@ There are many ways we can load a table. The first one involves loading the tabl
10911091
To load a table dynamically, we need to use the PERFORM statement with either subscripting or indexing. When doing this, we need to make sure that the data does not exceed the space allocated for the table. We will discuss file handling and the use of PERFORM clause in a later chapter. For example,
10921092

10931093
```COBOL
1094-
PROCEDURE DIVISION
1094+
PROCEDURE DIVISION.
10951095
...
10961096
PERFORM READ-FILE.
10971097
PERFORM VARYING SUB FROM 1 BY 1 UNTIL END-OF-FILE
@@ -1177,7 +1177,7 @@ We must ensure that the ODO object correctly specifies the number of occurrences
11771177
The following example shows how we can use an OCCURS DEPENDING ON clause:
11781178

11791179
```COBOL
1180-
WORKING-STORAGE SECTION
1180+
WORKING-STORAGE SECTION.
11811181
01 MAIN-AREA.
11821182
03 REC-1.
11831183
05 FIELD-1 PIC 9.
@@ -1763,8 +1763,8 @@ The code we have built so far is still not optimal, the repetition of the perfor
17631763
MOVE 'THE NUMBER IS: ' TO MSG-HEADER OF PRINT-REC.
17641764
17651765
PERFORM VARYING COUNTER FROM 01 BY 1 UNTIL COUNTER EQUAL 11
1766-
MOVE COUNTER TO MSG-TO-WRITE
1767-
WRITE PRINT-REC
1766+
MOVE COUNTER TO MSG-TO-WRITE
1767+
WRITE PRINT-REC
17681768
END-PERFORM.
17691769
17701770
CLOSE PRINT-LINE.
@@ -1899,8 +1899,8 @@ There is no requirement about the order that paragraphs should appear within a C
18991899
2000-READ-NEXT-RECORD.
19001900
PERFORM 4000-READ-RECORD
19011901
PERFORM UNTIL LASTREC = 'Y'
1902-
PERFORM 5000-WRITE-RECORD
1903-
PERFORM 4000-READ-RECORD
1902+
PERFORM 5000-WRITE-RECORD
1903+
PERFORM 4000-READ-RECORD
19041904
END-PERFORM.
19051905
*
19061906
3000-CLOSE-STOP.
@@ -1910,7 +1910,7 @@ There is no requirement about the order that paragraphs should appear within a C
19101910
*
19111911
4000-READ-RECORD.
19121912
READ ACCT-REC
1913-
AT END MOVE 'Y' TO LASTREC
1913+
AT END MOVE 'Y' TO LASTREC
19141914
END-READ.
19151915
*
19161916
5000-WRITE-RECORD.
@@ -1935,8 +1935,8 @@ There is no requirement about the order that paragraphs should appear within a C
19351935
2000-READ-NEXT-RECORD.
19361936
PERFORM 4000-READ-RECORD
19371937
PERFORM UNTIL LASTREC = 'Y'
1938-
PERFORM 5000-WRITE-RECORD
1939-
PERFORM 4000-READ-RECORD
1938+
PERFORM 5000-WRITE-RECORD
1939+
PERFORM 4000-READ-RECORD
19401940
END-PERFORM.
19411941
2000-READ-NEXT-RECORD-END.
19421942
```
@@ -1953,8 +1953,8 @@ Perhaps the simplest way of repeating a perform statement is to use the TIMES ke
19531953

19541954
```COBOL
19551955
PERFORM 10 TIMES
1956-
MOVE FIELD-A TO FIELD-B
1957-
WRITE RECORD
1956+
MOVE FIELD-A TO FIELD-B
1957+
WRITE RECORD
19581958
END-PERFORM.
19591959
```
19601960
*Example 10. TIMES*
@@ -2000,9 +2000,9 @@ Adding the UNTIL keyword to a perform sentence allows you to iterate over a grou
20002000
```COBOL
20012001
MOVE 0 TO COUNTER.
20022002
PERFORM UNTIL COUNTER = 10
2003-
ADD 1 TO COUNTER GIVING COUNTER
2004-
MOVE COUNTER TO MSG-TO-WRITE
2005-
WRITE PRINT-REC
2003+
ADD 1 TO COUNTER GIVING COUNTER
2004+
MOVE COUNTER TO MSG-TO-WRITE
2005+
WRITE PRINT-REC
20062006
END-PERFORM.
20072007
```
20082008
*Example 13. PERFORM UNTIL*
@@ -2024,9 +2024,9 @@ In this case, the Boolean condition is evaluated before the loop is executed. H
20242024

20252025
```COBOL
20262026
PERFORM WITH TEST AFTER UNTIL COUNTER = 10
2027-
ADD 1 TO COUNTER GIVING COUNTER
2028-
MOVE COUNTER TO MSG-TO-WRITE
2029-
WRITE PRINT-REC
2027+
ADD 1 TO COUNTER GIVING COUNTER
2028+
MOVE COUNTER TO MSG-TO-WRITE
2029+
WRITE PRINT-REC
20302030
END-PERFORM.
20312031
```
20322032
*Example 15. PERFORM WITH TEST AFTER UNTIL*
@@ -2490,7 +2490,7 @@ Observe in Example 1. 'The State is not Texas' is written as a result of the fi
24902490

24912491

24922492
```COBOL
2493-
WORKING-STORAGE.
2493+
WORKING-STORAGE SECTION.
24942494
01 USA-STATE PIC X(2) VALUE SPACES.
24952495
88 STATE VALUE 'TX'.
24962496
....
@@ -2521,7 +2521,7 @@ Other level number data-names require the condition expression to include a Bool
25212521

25222522

25232523
```COBOL
2524-
WORKING-STORAGE.
2524+
WORKING-STORAGE SECTION.
25252525
01 USA-STATE.
25262526
05 STATE PIC X(2) VALUE SPACES.
25272527
....
@@ -2610,7 +2610,7 @@ A PERFORM with UNTIL phrase is a conditional expression. In the UNTIL phrase fo
26102610

26112611

26122612
```COBOL
2613-
WORKING-STORAGE.
2613+
WORKING-STORAGE SECTION.
26142614
01 FACIAL-EXP PIC X(11) VALUE SPACES.
26152615
88 HAPPY VALUE 'HAPPY'.
26162616
....
@@ -2628,7 +2628,7 @@ END-PERFORM.
26282628
It is also possible to use PERFORM statement without the use of an 88-level conditional name, observe Example 6.
26292629

26302630
```COBOL
2631-
WORKING-STORAGE.
2631+
WORKING-STORAGE SECTION.
26322632
01 FACIAL-EXP PIC X(11) VALUE SPACES.
26332633
....
26342634
....
@@ -2647,7 +2647,7 @@ END-PERFORM.
26472647
The SEARCH statement searches a table for an element that satisfies the specified condition and adjusts the associated index to indicate that element. Tables, effectively an array of values, are created with an OCCURS clause applied to WORK-STORAGE data names. A WHEN clause is utilized in SEARCH statements to verify if the element searched for satisfies the specified condition. Assuming FACIAL-EXP has many possible values, then SEARCH WHEN is an alternative conditional expression, observe Example 7.
26482648

26492649
```COBOL
2650-
WORKING-STORAGE.
2650+
WORKING-STORAGE SECTION.
26512651
01 FACIAL-EXP-TABLE REDEFINES FACIAL-EXP-LIST.
26522652
05 FACIAL-EXP PIC X(11) OCCURS n TIMES INDEXED BY INX-A.
26532653
88 HAPPY VALUE "HAPPY".
@@ -2657,7 +2657,7 @@ PROCEDURE DIVISION.
26572657
....
26582658
....
26592659
SEARCH FACIAL-EXP
2660-
WHEN HAPPY(INX-A) DISPLAY 'I am glad you are happy'
2660+
WHEN HAPPY(INX-A) DISPLAY 'I am glad you are happy'
26612661
END-SEARCH
26622662
```
26632663
*Example 7. SEARCH WHEN statement*
@@ -3294,7 +3294,9 @@ Example 6 shows a usage of the COBOL function UPPER-CASE where a string or alpha
32943294
```COBOL
32953295
MOVE FUNCTION UPPER-CASE("This is shouting!") TO SOME-FIELD
32963296
DISPLAY SOME-FIELD
3297-
Output - THIS IS SHOUTING!
3297+
```
3298+
```
3299+
Output: THIS IS SHOUTING!
32983300
```
32993301

33003302
*Example 6. Character-handling intrinsic function*

0 commit comments

Comments
 (0)