MainframeMaster

COBOL Tutorial

COBOL ADVANCING Clause

Progress0 of 0 lessons

Introduction to ADVANCING Clause

The ADVANCING clause in COBOL is a powerful formatting control mechanism that manages line spacing and page advancement in output operations. It provides precise control over how output is positioned on pages, making it essential for creating professional reports, forms, and formatted displays.

The ADVANCING clause is primarily used with:

  • DISPLAY statements: For terminal and console output
  • WRITE statements: For file output formatting
  • Report generation: For professional document layout
  • Form printing: For structured data presentation
  • Page control: For multi-page document management

Understanding ADVANCING is crucial for creating well-formatted, professional-looking output in COBOL applications.

Basic ADVANCING Syntax and Structure

The ADVANCING clause follows a specific syntax that allows for flexible control over output positioning and spacing.

General Syntax

cobol
1
DISPLAY data-item [ADVANCING {BEFORE | AFTER} {n LINES | PAGE | mnemonic-name}]

Where:

  • BEFORE: Advance lines before displaying output (default)
  • AFTER: Advance lines after displaying output
  • n LINES: Advance a specific number of lines
  • PAGE: Advance to the next page
  • mnemonic-name: User-defined advancement value

Basic ADVANCING Examples

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
IDENTIFICATION DIVISION. PROGRAM-ID. ADVANCING-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 HEADER-LINE PIC X(50) VALUE "=== REPORT HEADER ===". 01 DATA-LINE PIC X(50) VALUE "This is a data line". 01 FOOTER-LINE PIC X(50) VALUE "=== REPORT FOOTER ===". PROCEDURE DIVISION. DISPLAY "Starting ADVANCING demonstration..." * Basic line advancement DISPLAY HEADER-LINE ADVANCING 2 LINES DISPLAY DATA-LINE ADVANCING 1 LINE DISPLAY DATA-LINE ADVANCING 1 LINE DISPLAY DATA-LINE ADVANCING 1 LINE * Page advancement DISPLAY "End of page 1" ADVANCING PAGE DISPLAY "Start of page 2" ADVANCING 2 LINES * Footer with spacing DISPLAY FOOTER-LINE ADVANCING 3 LINES DISPLAY "ADVANCING demonstration completed" STOP RUN.

BEFORE vs AFTER Advancement

Understanding the difference between BEFORE and AFTER advancement is crucial for proper output positioning and formatting control.

BEFORE Advancement (Default)

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
IDENTIFICATION DIVISION. PROGRAM-ID. BEFORE-ADVANCING-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 OUTPUT-LINE PIC X(40). PROCEDURE DIVISION. DISPLAY "=== BEFORE ADVANCING DEMONSTRATION ===" DISPLAY "Line 1 - No advancement" * BEFORE advancement (default behavior) MOVE "Line 2 - BEFORE 2 lines" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING BEFORE 2 LINES MOVE "Line 3 - BEFORE 1 line" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING BEFORE 1 LINE MOVE "Line 4 - BEFORE 3 lines" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING BEFORE 3 LINES DISPLAY "End of BEFORE demonstration" STOP RUN.

AFTER Advancement

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
IDENTIFICATION DIVISION. PROGRAM-ID. AFTER-ADVANCING-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 OUTPUT-LINE PIC X(40). PROCEDURE DIVISION. DISPLAY "=== AFTER ADVANCING DEMONSTRATION ===" DISPLAY "Line 1 - No advancement" * AFTER advancement MOVE "Line 2 - AFTER 2 lines" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING AFTER 2 LINES MOVE "Line 3 - AFTER 1 line" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING AFTER 1 LINE MOVE "Line 4 - AFTER 3 lines" TO OUTPUT-LINE DISPLAY OUTPUT-LINE ADVANCING AFTER 3 LINES DISPLAY "End of AFTER demonstration" STOP RUN.

Comparison Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
PROCEDURE DIVISION. DISPLAY "=== BEFORE vs AFTER COMPARISON ===" DISPLAY "Original line" * BEFORE advancement DISPLAY "BEFORE 2 lines" ADVANCING BEFORE 2 LINES DISPLAY "This appears after 2 blank lines above" DISPLAY " " * AFTER advancement DISPLAY "AFTER 2 lines" ADVANCING AFTER 2 LINES DISPLAY "This appears after 2 blank lines above" STOP RUN.

Page Control with ADVANCING

Page control is one of the most important uses of the ADVANCING clause, enabling the creation of multi-page documents with proper page breaks and headers.

Basic Page Control

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
IDENTIFICATION DIVISION. PROGRAM-ID. PAGE-CONTROL-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. 01 PAGE-HEADER. 05 FILLER PIC X(20) VALUE "PAGE ". 05 PAGE-NUMBER PIC 9(3). 05 FILLER PIC X(20) VALUE " - REPORT TITLE". 05 FILLER PIC X(30) VALUE SPACES. 01 PAGE-FOOTER. 05 FILLER PIC X(20) VALUE "End of Page ". 05 FOOTER-PAGE PIC 9(3). 05 FILLER PIC X(50) VALUE SPACES. 01 DATA-LINE PIC X(60). 01 CURRENT-PAGE PIC 9(3) VALUE 1. PROCEDURE DIVISION. PERFORM DISPLAY-PAGE-HEADER PERFORM DISPLAY-PAGE-CONTENT PERFORM DISPLAY-PAGE-FOOTER PERFORM ADVANCE-TO-NEXT-PAGE PERFORM DISPLAY-PAGE-HEADER PERFORM DISPLAY-PAGE-CONTENT PERFORM DISPLAY-PAGE-FOOTER STOP RUN. DISPLAY-PAGE-HEADER. MOVE CURRENT-PAGE TO PAGE-NUMBER DISPLAY PAGE-HEADER ADVANCING PAGE DISPLAY " " ADVANCING 1 LINE DISPLAY "Report generated on: " FUNCTION CURRENT-DATE DISPLAY " " ADVANCING 1 LINE. DISPLAY-PAGE-CONTENT. MOVE "This is sample content for the report." TO DATA-LINE DISPLAY DATA-LINE ADVANCING 1 LINE MOVE "Additional data lines would appear here." TO DATA-LINE DISPLAY DATA-LINE ADVANCING 1 LINE MOVE "More content to fill the page..." TO DATA-LINE DISPLAY DATA-LINE ADVANCING 1 LINE. DISPLAY-PAGE-FOOTER. DISPLAY " " ADVANCING 2 LINES MOVE CURRENT-PAGE TO FOOTER-PAGE DISPLAY PAGE-FOOTER ADVANCING 1 LINE. ADVANCE-TO-NEXT-PAGE. ADD 1 TO CURRENT-PAGE.

Advanced Page Control with Line Counting

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
IDENTIFICATION DIVISION. PROGRAM-ID. ADVANCED-PAGE-CONTROL. DATA DIVISION. WORKING-STORAGE SECTION. 01 PAGE-CONTROL. 05 CURRENT-PAGE PIC 9(3) VALUE 1. 05 CURRENT-LINE PIC 9(3) VALUE 0. 05 MAX-LINES-PER-PAGE PIC 9(3) VALUE 50. 05 LINES-REMAINING PIC 9(3). 01 REPORT-DATA. 05 DATA-LINE PIC X(60). 05 LINE-COUNTER PIC 9(3) VALUE 0. PROCEDURE DIVISION. PERFORM INITIALIZE-PAGE-CONTROL PERFORM PROCESS-REPORT-DATA STOP RUN. INITIALIZE-PAGE-CONTROL. DISPLAY "=== Advanced Page Control Demo ===" PERFORM DISPLAY-PAGE-HEADER. PROCESS-REPORT-DATA. PERFORM VARYING LINE-COUNTER FROM 1 BY 1 UNTIL LINE-COUNTER > 100 PERFORM CHECK-PAGE-BOUNDARIES PERFORM DISPLAY-DATA-LINE END-PERFORM. CHECK-PAGE-BOUNDARIES. ADD 1 TO CURRENT-LINE IF CURRENT-LINE > MAX-LINES-PER-PAGE PERFORM DISPLAY-PAGE-FOOTER PERFORM ADVANCE-TO-NEXT-PAGE PERFORM DISPLAY-PAGE-HEADER MOVE 1 TO CURRENT-LINE END-IF. DISPLAY-DATA-LINE. STRING "Line " DELIMITED BY SIZE LINE-COUNTER DELIMITED BY SIZE " - Sample data content" DELIMITED BY SIZE INTO DATA-LINE DISPLAY DATA-LINE ADVANCING 1 LINE. DISPLAY-PAGE-HEADER. DISPLAY "PAGE " CURRENT-PAGE " - REPORT HEADER" ADVANCING PAGE DISPLAY "Generated: " FUNCTION CURRENT-DATE ADVANCING 1 LINE DISPLAY " " ADVANCING 1 LINE. DISPLAY-PAGE-FOOTER. DISPLAY " " ADVANCING 2 LINES DISPLAY "End of Page " CURRENT-PAGE ADVANCING 1 LINE. ADVANCE-TO-NEXT-PAGE. ADD 1 TO CURRENT-PAGE MOVE 0 TO CURRENT-LINE.

Mnemonic Names for ADVANCING

Mnemonic names allow you to define custom advancement values that can be referenced by name, making code more readable and maintainable.

Defining and Using Mnemonic Names

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
IDENTIFICATION DIVISION. PROGRAM-ID. MNEMONIC-ADVANCING-DEMO. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SINGLE-SPACE IS ADVANCE-1 DOUBLE-SPACE IS ADVANCE-2 TRIPLE-SPACE IS ADVANCE-3 QUADRUPLE-SPACE IS ADVANCE-4 SECTION-BREAK IS ADVANCE-5 PAGE-BREAK IS ADVANCE-PAGE. DATA DIVISION. WORKING-STORAGE SECTION. 01 REPORT-SECTIONS. 05 HEADER-LINE PIC X(50) VALUE "=== SECTION HEADER ===". 05 DATA-LINE PIC X(50) VALUE "Data line content". 05 FOOTER-LINE PIC X(50) VALUE "=== SECTION FOOTER ===". PROCEDURE DIVISION. DISPLAY "=== Mnemonic ADVANCING Demonstration ===" * Using mnemonic names for spacing DISPLAY HEADER-LINE ADVANCING ADVANCE-2 DISPLAY DATA-LINE ADVANCING ADVANCE-1 DISPLAY DATA-LINE ADVANCING ADVANCE-1 DISPLAY DATA-LINE ADVANCING ADVANCE-1 * Section break DISPLAY " " ADVANCING SECTION-BREAK DISPLAY "New section starts here" ADVANCING ADVANCE-2 * More data with different spacing DISPLAY DATA-LINE ADVANCING ADVANCE-1 DISPLAY DATA-LINE ADVANCING ADVANCE-1 * Page break DISPLAY "End of section" ADVANCING PAGE-BREAK DISPLAY "New page starts here" ADVANCING ADVANCE-3 DISPLAY FOOTER-LINE ADVANCING ADVANCE-2 STOP RUN.

Professional Report Formatting

The ADVANCING clause is essential for creating professional reports with proper spacing, headers, footers, and page breaks.

Complete Report Example

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
IDENTIFICATION DIVISION. PROGRAM-ID. PROFESSIONAL-REPORT. ENVIRONMENT DIVISION. CONFIGURATION SECTION. SPECIAL-NAMES. SINGLE-SPACE IS SPACE-1 DOUBLE-SPACE IS SPACE-2 TRIPLE-SPACE IS SPACE-3 PAGE-BREAK IS NEW-PAGE. DATA DIVISION. WORKING-STORAGE SECTION. 01 REPORT-HEADER. 05 COMPANY-NAME PIC X(30) VALUE "ACME CORPORATION". 05 REPORT-TITLE PIC X(30) VALUE "MONTHLY SALES REPORT". 05 REPORT-DATE PIC X(20). 01 PAGE-HEADER. 05 FILLER PIC X(15) VALUE "PAGE: ". 05 PAGE-NUMBER PIC 9(3). 05 FILLER PIC X(20) VALUE "DATE: ". 05 HEADER-DATE PIC X(10). 01 COLUMN-HEADERS. 05 FILLER PIC X(8) VALUE "CUST-ID". 05 FILLER PIC X(15) VALUE "CUSTOMER NAME". 05 FILLER PIC X(12) VALUE "SALES AMOUNT". 05 FILLER PIC X(10) VALUE "REGION". 01 DETAIL-LINE. 05 CUSTOMER-ID PIC X(8). 05 CUSTOMER-NAME PIC X(15). 05 SALES-AMOUNT PIC $$$,$$9.99. 05 REGION-CODE PIC X(10). 01 SUMMARY-LINE. 05 FILLER PIC X(20) VALUE "TOTAL SALES: $". 05 TOTAL-SALES PIC $$$,$$$,$$9.99. 01 PAGE-CONTROL. 05 CURRENT-PAGE PIC 9(3) VALUE 1. 05 CURRENT-LINE PIC 9(3) VALUE 0. 05 MAX-LINES PIC 9(3) VALUE 45. PROCEDURE DIVISION. PERFORM INITIALIZE-REPORT PERFORM DISPLAY-REPORT-HEADER PERFORM DISPLAY-PAGE-HEADER PERFORM PROCESS-SALES-DATA PERFORM DISPLAY-SUMMARY STOP RUN. INITIALIZE-REPORT. MOVE FUNCTION CURRENT-DATE(1:8) TO REPORT-DATE MOVE FUNCTION CURRENT-DATE(1:8) TO HEADER-DATE. DISPLAY-REPORT-HEADER. DISPLAY COMPANY-NAME ADVANCING NEW-PAGE DISPLAY REPORT-TITLE ADVANCING SPACE-2 DISPLAY "Report Date: " REPORT-DATE ADVANCING SPACE-3. DISPLAY-PAGE-HEADER. MOVE CURRENT-PAGE TO PAGE-NUMBER DISPLAY PAGE-HEADER ADVANCING SPACE-1 DISPLAY " " ADVANCING SPACE-1 DISPLAY COLUMN-HEADERS ADVANCING SPACE-1 DISPLAY " " ADVANCING SPACE-1 MOVE 5 TO CURRENT-LINE. PROCESS-SALES-DATA. * Simulate processing sales data PERFORM VARYING CURRENT-LINE FROM 6 BY 1 UNTIL CURRENT-LINE > 40 PERFORM GENERATE-SAMPLE-DATA PERFORM DISPLAY-DETAIL-LINE PERFORM CHECK-PAGE-BOUNDARY END-PERFORM. GENERATE-SAMPLE-DATA. * Generate sample customer data STRING "CUST" DELIMITED BY SIZE CURRENT-LINE DELIMITED BY SIZE INTO CUSTOMER-ID STRING "Customer " DELIMITED BY SIZE CURRENT-LINE DELIMITED BY SIZE INTO CUSTOMER-NAME COMPUTE SALES-AMOUNT = CURRENT-LINE * 100.50 MOVE "REGION-A" TO REGION-CODE. DISPLAY-DETAIL-LINE. DISPLAY DETAIL-LINE ADVANCING SPACE-1. CHECK-PAGE-BOUNDARY. IF CURRENT-LINE >= MAX-LINES PERFORM DISPLAY-PAGE-FOOTER ADD 1 TO CURRENT-PAGE PERFORM DISPLAY-PAGE-HEADER END-IF. DISPLAY-PAGE-FOOTER. DISPLAY " " ADVANCING SPACE-2 DISPLAY "End of Page " CURRENT-PAGE ADVANCING SPACE-1. DISPLAY-SUMMARY. COMPUTE TOTAL-SALES = 40 * 100.50 * 20.25 DISPLAY " " ADVANCING SPACE-3 DISPLAY SUMMARY-LINE ADVANCING SPACE-2 DISPLAY "Report completed successfully" ADVANCING SPACE-1.

ADVANCING with WRITE Statements

The ADVANCING clause can also be used with WRITE statements for file output formatting, providing control over how data is written to files.

File Output with ADVANCING

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
IDENTIFICATION DIVISION. PROGRAM-ID. FILE-ADVANCING-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT REPORT-FILE ASSIGN TO "REPORT.OUT" ORGANIZATION IS SEQUENTIAL ACCESS MODE IS SEQUENTIAL FILE STATUS IS FILE-STATUS. DATA DIVISION. FILE SECTION. FD REPORT-FILE. 01 REPORT-RECORD. 05 RECORD-DATA PIC X(80). WORKING-STORAGE SECTION. 01 FILE-STATUS PIC X(2). 01 REPORT-LINE PIC X(80). 01 LINE-COUNTER PIC 9(3) VALUE 0. PROCEDURE DIVISION. PERFORM OPEN-REPORT-FILE PERFORM WRITE-REPORT-CONTENT PERFORM CLOSE-REPORT-FILE STOP RUN. OPEN-REPORT-FILE. OPEN OUTPUT REPORT-FILE IF FILE-STATUS NOT = "00" DISPLAY "Error opening report file: " FILE-STATUS STOP RUN END-IF DISPLAY "Report file opened successfully". WRITE-REPORT-CONTENT. * Write header with spacing MOVE "=== REPORT HEADER ===" TO REPORT-LINE WRITE REPORT-RECORD FROM REPORT-LINE AFTER ADVANCING 2 LINES * Write data lines MOVE "Data line 1" TO REPORT-LINE WRITE REPORT-RECORD FROM REPORT-LINE AFTER ADVANCING 1 LINE MOVE "Data line 2" TO REPORT-LINE WRITE REPORT-RECORD FROM REPORT-LINE AFTER ADVANCING 1 LINE MOVE "Data line 3" TO REPORT-LINE WRITE REPORT-RECORD FROM REPORT-LINE AFTER ADVANCING 1 LINE * Write footer with spacing MOVE "=== REPORT FOOTER ===" TO REPORT-LINE WRITE REPORT-RECORD FROM REPORT-LINE AFTER ADVANCING 3 LINES. CLOSE-REPORT-FILE. CLOSE REPORT-FILE DISPLAY "Report file closed successfully".

Best Practices for ADVANCING Usage

Following best practices ensures consistent, maintainable, and professional output formatting when using the ADVANCING clause.

Design Guidelines

  • Use mnemonic names for common spacing values
  • Plan page layouts before implementing
  • Consider different output devices and their limitations
  • Test formatting with realistic data volumes
  • Document spacing requirements and standards

Implementation Best Practices

  • Consistent use of BEFORE vs AFTER advancement
  • Proper page break management for long reports
  • Appropriate spacing for readability
  • Error handling for output device limitations
  • Performance consideration for high-volume output

Maintenance Considerations

  • Centralize formatting constants and mnemonic names
  • Regular testing with different output devices
  • Documentation of formatting standards
  • Version control for formatting changes
  • User feedback incorporation for readability improvements

Exercise: Professional Report Generator

Create a comprehensive report generator that demonstrates advanced ADVANCING usage. The system should include:

  • Multi-page report generation with proper page breaks
  • Professional headers and footers
  • Consistent spacing and formatting
  • Mnemonic names for all spacing values
  • Both console and file output capabilities

Consider these advanced requirements:

  • How would you handle different page sizes and orientations?
  • What strategies would you use for dynamic content spacing?
  • How would you implement conditional page breaks?
  • What formatting options would you provide for different report types?

FAQ

What is the ADVANCING clause in COBOL?

The ADVANCING clause in COBOL controls line spacing and page advancement in output operations. It specifies how many lines to advance before or after displaying output, enabling precise control over report formatting and page layout.

How do you use ADVANCING in COBOL DISPLAY statements?

ADVANCING is used with DISPLAY statements to control line spacing. Syntax: 'DISPLAY data-item ADVANCING n LINES' advances n lines before displaying, or 'DISPLAY data-item ADVANCING PAGE' advances to the next page.

What are the different ADVANCING options in COBOL?

ADVANCING options include: BEFORE (advance before output), AFTER (advance after output), LINES (advance specific number of lines), PAGE (advance to next page), and mnemonic-name (user-defined advancement).

How do you control page breaks with ADVANCING?

Page breaks are controlled using 'ADVANCING PAGE' which advances to the next page before or after output. This is commonly used in report generation to start new pages at specific points.

What is the difference between BEFORE and AFTER in ADVANCING?

BEFORE advances lines before displaying the output, while AFTER advances lines after displaying the output. BEFORE is the default if not specified. The choice affects the positioning of the output relative to the advancement.