MainframeMaster

COBOL Tutorial

COBOL EJECT Clause - Quick Reference

Progress0 of 0 lessons

Overview

The EJECT clause is a standalone statement used to send a form feed character to the output device, causing a page break or new page. It is commonly used for printer control and report formatting to ensure proper page separation.

Purpose and Usage

  • Page control - Force page breaks in output
  • Report formatting - Control report layout and structure
  • Printer control - Manage printer page advancement
  • Output separation - Separate different sections of output
  • Form feed - Send form feed character to devices

Page Ejection Concept

Current Page Content
EJECT → Form Feed Character (0x0C)
New Page Starts
Page break or form feed sent to output device

EJECT sends a form feed character to cause a page break.

Syntax

The EJECT clause follows a simple syntax pattern and is used as a standalone statement in the PROCEDURE DIVISION.

Basic Syntax

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
* Basic EJECT syntax EJECT * In context with other statements DISPLAY "End of page content" EJECT DISPLAY "Start of new page content" * With conditional logic IF PAGE-NUMBER > 50 EJECT MOVE 1 TO PAGE-NUMBER END-IF * In report generation DISPLAY "Report Header" EJECT DISPLAY "Report Body"

EJECT is a simple standalone statement that requires no parameters.

EJECT vs ADVANCING PAGE

FeatureEJECTADVANCING PAGE
UsageStandalone statementClause with WRITE
ContextGeneral output controlFile writing operations
EffectImmediate page breakPage break with data
FlexibilitySimple and directIntegrated with file I/O

Form Feed Character

cobol
1
2
3
4
5
6
7
8
9
* EJECT sends form feed character * ASCII: 12 (decimal) * Hex: 0C * Control character: FF (Form Feed) * Equivalent operations: EJECT * COBOL EJECT statement DISPLAY X"0C" UPON PRINTER * Manual form feed WRITE RECORD AFTER ADVANCING PAGE * With WRITE

EJECT sends a form feed character (0x0C) to the output device.

Practical Examples

These examples demonstrate how to use the EJECT clause effectively in different output scenarios.

Basic Report Generation

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. BASIC-REPORT-EJECT. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-PAGE-NUMBER PIC 9(3) VALUE 1. 01 WS-LINE-COUNT PIC 9(2) VALUE 0. 01 WS-MAX-LINES PIC 9(2) VALUE 60. PROCEDURE DIVISION. MAIN-PROCESS. * Print report header DISPLAY "SALES REPORT" UPON PRINTER DISPLAY "Page: " WS-PAGE-NUMBER UPON PRINTER DISPLAY "Date: " FUNCTION CURRENT-DATE UPON PRINTER DISPLAY " " UPON PRINTER * Print report content PERFORM PRINT-REPORT-CONTENT * Eject to new page for summary EJECT DISPLAY "REPORT SUMMARY" UPON PRINTER DISPLAY "Total pages: " WS-PAGE-NUMBER UPON PRINTER STOP RUN. PRINT-REPORT-CONTENT. * Simulate printing report lines PERFORM VARYING WS-LINE-COUNT FROM 1 BY 1 UNTIL WS-LINE-COUNT > 50 DISPLAY "Line " WS-LINE-COUNT " content" UPON PRINTER * Check if page is full IF WS-LINE-COUNT = WS-MAX-LINES EJECT ADD 1 TO WS-PAGE-NUMBER MOVE 0 TO WS-LINE-COUNT DISPLAY "Page: " WS-PAGE-NUMBER UPON PRINTER END-IF END-PERFORM.

Basic report generation using EJECT for page breaks and formatting.

Multi-Section Report

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
IDENTIFICATION DIVISION. PROGRAM-ID. MULTI-SECTION-REPORT. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-SECTION-COUNT PIC 9(2) VALUE 0. PROCEDURE DIVISION. MAIN-PROCESS. * Print title page DISPLAY "COMPANY ANNUAL REPORT" UPON PRINTER DISPLAY "Year: 2024" UPON PRINTER DISPLAY " " UPON PRINTER DISPLAY "Prepared by: Finance Department" UPON PRINTER * Eject to start first section EJECT * Print financial summary section PERFORM PRINT-FINANCIAL-SUMMARY * Eject to start second section EJECT * Print operational summary section PERFORM PRINT-OPERATIONAL-SUMMARY * Eject to start third section EJECT * Print conclusions section PERFORM PRINT-CONCLUSIONS STOP RUN. PRINT-FINANCIAL-SUMMARY. DISPLAY "FINANCIAL SUMMARY" UPON PRINTER DISPLAY "==================" UPON PRINTER DISPLAY "Revenue: $1,000,000" UPON PRINTER DISPLAY "Expenses: $750,000" UPON PRINTER DISPLAY "Net Profit: $250,000" UPON PRINTER. PRINT-OPERATIONAL-SUMMARY. DISPLAY "OPERATIONAL SUMMARY" UPON PRINTER DISPLAY "===================" UPON PRINTER DISPLAY "Employees: 150" UPON PRINTER DISPLAY "Locations: 5" UPON PRINTER DISPLAY "Projects: 25" UPON PRINTER. PRINT-CONCLUSIONS. DISPLAY "CONCLUSIONS" UPON PRINTER DISPLAY "===========" UPON PRINTER DISPLAY "The company performed well in 2024." UPON PRINTER DISPLAY "Recommendations for 2025:" UPON PRINTER DISPLAY "- Expand operations" UPON PRINTER DISPLAY "- Increase marketing budget" UPON PRINTER.

Multi-section report using EJECT to separate different report sections.

Conditional Page Ejection

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
IDENTIFICATION DIVISION. PROGRAM-ID. CONDITIONAL-EJECT. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-LINE-COUNT PIC 9(3) VALUE 0. 01 WS-PAGE-NUMBER PIC 9(3) VALUE 1. 01 WS-MAX-LINES PIC 9(3) VALUE 55. 01 WS-RECORD-COUNT PIC 9(5) VALUE 0. PROCEDURE DIVISION. MAIN-PROCESS. * Print header PERFORM PRINT-PAGE-HEADER * Process records PERFORM PROCESS-RECORDS UNTIL WS-RECORD-COUNT > 1000 STOP RUN. PRINT-PAGE-HEADER. DISPLAY "CUSTOMER LISTING" UPON PRINTER DISPLAY "Page: " WS-PAGE-NUMBER UPON PRINTER DISPLAY "Date: " FUNCTION CURRENT-DATE UPON PRINTER DISPLAY " " UPON PRINTER DISPLAY "Customer ID | Name | Balance" UPON PRINTER DISPLAY "------------|------|--------" UPON PRINTER MOVE 0 TO WS-LINE-COUNT. PROCESS-RECORDS. ADD 1 TO WS-RECORD-COUNT ADD 1 TO WS-LINE-COUNT * Print record (simulated) DISPLAY "CUST" WS-RECORD-COUNT " | Customer " WS-RECORD-COUNT " | $1000" UPON PRINTER * Check if page is full IF WS-LINE-COUNT >= WS-MAX-LINES EJECT ADD 1 TO WS-PAGE-NUMBER PERFORM PRINT-PAGE-HEADER END-IF * Check if we need a new page for new section IF WS-RECORD-COUNT = 500 EJECT DISPLAY "MID-YEAR SUMMARY" UPON PRINTER DISPLAY "Records processed: " WS-RECORD-COUNT UPON PRINTER EJECT PERFORM PRINT-PAGE-HEADER END-IF.

Conditional page ejection based on line count and record processing.

Error Handling with EJECT

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
IDENTIFICATION DIVISION. PROGRAM-ID. ERROR-HANDLING-EJECT. DATA DIVISION. WORKING-STORAGE SECTION. 01 WS-ERROR-COUNT PIC 9(3) VALUE 0. 01 WS-SUCCESS-COUNT PIC 9(3) VALUE 0. 01 WS-PAGE-NUMBER PIC 9(3) VALUE 1. PROCEDURE DIVISION. MAIN-PROCESS. * Print success report DISPLAY "SUCCESS REPORT" UPON PRINTER DISPLAY "Page: " WS-PAGE-NUMBER UPON PRINTER PERFORM PRINT-SUCCESS-DETAILS * Eject to error section if errors exist IF WS-ERROR-COUNT > 0 EJECT DISPLAY "ERROR REPORT" UPON PRINTER DISPLAY "Page: " WS-PAGE-NUMBER UPON PRINTER PERFORM PRINT-ERROR-DETAILS END-IF * Eject to summary page EJECT DISPLAY "PROCESSING SUMMARY" UPON PRINTER DISPLAY "Successful operations: " WS-SUCCESS-COUNT UPON PRINTER DISPLAY "Errors encountered: " WS-ERROR-COUNT UPON PRINTER STOP RUN. PRINT-SUCCESS-DETAILS. DISPLAY "Successful operations:" UPON PRINTER DISPLAY "Operation 1: Completed" UPON PRINTER DISPLAY "Operation 2: Completed" UPON PRINTER ADD 2 TO WS-SUCCESS-COUNT. PRINT-ERROR-DETAILS. DISPLAY "Error details:" UPON PRINTER DISPLAY "Error 1: File not found" UPON PRINTER DISPLAY "Error 2: Invalid data" UPON PRINTER ADD 2 TO WS-ERROR-COUNT.

Error handling using EJECT to separate success and error reports.

Best Practices and Considerations

Understanding best practices ensures proper page control and report formatting.

EJECT Best Practices

  • Use strategically - Eject only when necessary for formatting
  • Count lines - Track line count to avoid excessive page breaks
  • Plan layout - Design report structure before implementing EJECT
  • Test output - Verify EJECT behavior on target devices
  • Consider alternatives - Use ADVANCING PAGE when writing to files

Common Pitfalls to Avoid

PitfallProblemSolution
Excessive ejectionToo many blank pagesUse line counting
Wrong deviceNo effect on non-page devicesCheck device capabilities
Poor timingBreaks in wrong placesPlan page breaks carefully
Missing headersPages without identificationPrint headers after EJECT
Inconsistent usagePoor report formattingUse consistent page control

Device Compatibility

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
* Printer devices (most compatible) EJECT * Works with most printers * Terminal/console devices EJECT * May clear screen or have no effect * File output EJECT * May insert form feed character in file * Network printers EJECT * Depends on printer driver * Virtual devices EJECT * Behavior varies by implementation

EJECT behavior varies depending on the output device and implementation.

EJECT Clause Quick Reference

UsageSyntaxExample
Basic page breakEJECTEJECT
After contentDISPLAY content; EJECTDISPLAY "End"; EJECT
ConditionalIF condition EJECT END-IFIF LINE-COUNT > 50 EJECT END-IF
Section separatorEJECT; DISPLAY new-sectionEJECT; DISPLAY "NEW SECTION"
Report formattingEJECT; PRINT-HEADEREJECT; PERFORM PRINT-HEADER

Test Your Knowledge

1. What is the primary purpose of the EJECT clause in COBOL?

  • To eject files from memory
  • To eject a page or form feed in output
  • To eject data from variables
  • To eject programs from execution

2. Where is the EJECT clause typically used?

  • In the IDENTIFICATION DIVISION
  • In the ENVIRONMENT DIVISION
  • In the PROCEDURE DIVISION for output control
  • In the DATA DIVISION

3. What happens when EJECT is executed?

  • The program stops
  • A page break or form feed is sent to the output device
  • Data is deleted
  • A file is closed

4. Which output devices typically respond to EJECT?

  • Only printers
  • Only screens
  • Printers and other page-oriented devices
  • All devices

5. How does EJECT differ from ADVANCING PAGE?

  • They are the same thing
  • EJECT is for files, ADVANCING PAGE is for displays
  • EJECT is a standalone statement, ADVANCING PAGE is a clause
  • EJECT is deprecated, ADVANCING PAGE is modern

Frequently Asked Questions