The LINE-COUNTER special register is used in COBOL to track the current line number on a page during report generation. It works in conjunction with the LINAGE clause and LINAGE-COUNTER to provide automatic page formatting and line counting capabilities.
LINE-COUNTER automatically tracks line numbers and resets on page breaks.
LINE-COUNTER is a special register that can be used directly in COBOL statements without declaration. It works with the LINAGE clause for proper page formatting.
1234567891011121314151617181920* LINE-COUNTER is used directly as a special register * No declaration needed - it's built into COBOL * Example usage in conditional statements IF LINE-COUNTER > 50 PERFORM WRITE-HEADER END-IF * Example usage in calculations COMPUTE REMAINING-LINES = LINAGE-COUNTER - LINE-COUNTER * Example usage in display statements DISPLAY "Current line: " LINE-COUNTER * Example usage with LINAGE clause FD REPORT-FILE LINAGE IS 60 LINES WITH FOOTING AT 55 LINES AT TOP 5 LINES AT BOTTOM 5.
LINE-COUNTER is a built-in special register that requires no declaration.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778* Complete example using LINE-COUNTER IDENTIFICATION DIVISION. PROGRAM-ID. LINE-COUNTER-DEMO. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT REPORT-FILE ASSIGN TO "REPORT.TXT" ORGANIZATION IS LINE SEQUENTIAL. DATA DIVISION. FILE SECTION. FD REPORT-FILE LINAGE IS 60 LINES WITH FOOTING AT 55 LINES AT TOP 5 LINES AT BOTTOM 5. 01 REPORT-LINE. 05 LINE-CONTENT PIC X(80). WORKING-STORAGE SECTION. 01 DATA-RECORD. 05 RECORD-ID PIC 9(6). 05 RECORD-NAME PIC X(30). 05 RECORD-VALUE PIC 9(8)V99. 01 PAGE-NUMBER PIC 9(3) VALUE 1. 01 REMAINING-LINES PIC 9(2). PROCEDURE DIVISION. MAIN-LOGIC. OPEN OUTPUT REPORT-FILE PERFORM WRITE-REPORT-HEADER PERFORM PROCESS-DATA CLOSE REPORT-FILE STOP RUN. WRITE-REPORT-HEADER. * Write header at top of page MOVE "REPORT HEADER - PAGE " TO LINE-CONTENT MOVE PAGE-NUMBER TO LINE-CONTENT(20:3) WRITE REPORT-LINE * LINE-COUNTER is now 1 MOVE "DATE: " TO LINE-CONTENT MOVE FUNCTION CURRENT-DATE TO LINE-CONTENT(7:8) WRITE REPORT-LINE * LINE-COUNTER is now 2. PROCESS-DATA. * Process data records PERFORM UNTIL END-OF-DATA READ DATA-FILE AT END SET END-OF-DATA TO TRUE END-READ * Check if we need a new page IF LINE-COUNTER > 50 PERFORM NEW-PAGE END-IF * Write data line PERFORM WRITE-DATA-LINE END-PERFORM. NEW-PAGE. * Start new page ADD 1 TO PAGE-NUMBER PERFORM WRITE-REPORT-HEADER * LINE-COUNTER is automatically reset to 1. WRITE-DATA-LINE. * Write data line MOVE RECORD-ID TO LINE-CONTENT(1:6) MOVE RECORD-NAME TO LINE-CONTENT(8:30) MOVE RECORD-VALUE TO LINE-CONTENT(40:10) WRITE REPORT-LINE * LINE-COUNTER is automatically incremented.
This example shows how LINE-COUNTER is used with LINAGE for page formatting.
12345678910111213141516171819202122232425* LINAGE clause with LINE-COUNTER FD REPORT-FILE LINAGE IS 60 LINES * Total lines per page WITH FOOTING AT 55 * Footer starts at line 55 LINES AT TOP 5 * Header area (lines 1-5) LINES AT BOTTOM 5. * Footer area (lines 56-60) * LINE-COUNTER behavior with this LINAGE: * - Starts at 1 for each page * - Increments with each WRITE statement * - Resets to 1 when page is full (line 60) * - Can be used to check current position * Example usage: IF LINE-COUNTER = 1 PERFORM WRITE-PAGE-HEADER END-IF IF LINE-COUNTER = 55 PERFORM WRITE-PAGE-FOOTER END-IF IF LINE-COUNTER > 50 PERFORM NEW-PAGE END-IF
The LINAGE clause defines page layout parameters that LINE-COUNTER works within.
LINE-COUNTER is essential in various scenarios where proper page formatting and line tracking are critical for report generation.
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778* Report generation with LINE-COUNTER IDENTIFICATION DIVISION. PROGRAM-ID. REPORT-GENERATOR. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT REPORT-FILE ASSIGN TO "SALES-REPORT.TXT" ORGANIZATION IS LINE SEQUENTIAL. DATA DIVISION. FILE SECTION. FD REPORT-FILE LINAGE IS 66 LINES WITH FOOTING AT 60 LINES AT TOP 6 LINES AT BOTTOM 6. 01 REPORT-LINE. 05 LINE-CONTENT PIC X(132). WORKING-STORAGE SECTION. 01 SALES-RECORD. 05 SALES-DATE PIC 9(8). 05 SALES-AMOUNT PIC 9(8)V99. 05 SALES-REGION PIC X(20). 01 PAGE-NUMBER PIC 9(3) VALUE 1. 01 TOTAL-SALES PIC 9(10)V99 VALUE ZERO. PROCEDURE DIVISION. MAIN-LOGIC. OPEN OUTPUT REPORT-FILE PERFORM WRITE-REPORT-HEADER PERFORM PROCESS-SALES-DATA PERFORM WRITE-REPORT-FOOTER CLOSE REPORT-FILE STOP RUN. WRITE-REPORT-HEADER. * Write header only at top of page IF LINE-COUNTER = 1 MOVE "SALES REPORT" TO LINE-CONTENT WRITE REPORT-LINE MOVE "PAGE " TO LINE-CONTENT(1:5) MOVE PAGE-NUMBER TO LINE-CONTENT(6:3) WRITE REPORT-LINE MOVE SPACES TO LINE-CONTENT WRITE REPORT-LINE END-IF. PROCESS-SALES-DATA. * Process sales data with page breaks PERFORM UNTIL END-OF-SALES-DATA READ SALES-FILE AT END SET END-OF-SALES-DATA TO TRUE END-READ * Check if page is getting full IF LINE-COUNTER > 55 PERFORM NEW-PAGE END-IF * Write sales data PERFORM WRITE-SALES-LINE END-PERFORM. NEW-PAGE. * Start new page ADD 1 TO PAGE-NUMBER PERFORM WRITE-REPORT-HEADER. WRITE-SALES-LINE. * Write sales data line MOVE SALES-DATE TO LINE-CONTENT(1:8) MOVE SALES-AMOUNT TO LINE-CONTENT(10:10) MOVE SALES-REGION TO LINE-CONTENT(22:20) WRITE REPORT-LINE ADD SALES-AMOUNT TO TOTAL-SALES.
Report generation uses LINE-COUNTER for proper page formatting and headers.
1234567891011121314151617181920212223242526272829303132333435363738* Page break management with LINE-COUNTER IDENTIFICATION DIVISION. PROGRAM-ID. PAGE-BREAK-MANAGER. DATA DIVISION. WORKING-STORAGE SECTION. 01 CURRENT-LINE PIC 9(2). 01 LINES-PER-PAGE PIC 9(2) VALUE 60. 01 FOOTER-START PIC 9(2) VALUE 55. 01 HEADER-LINES PIC 9(2) VALUE 5. PROCEDURE DIVISION. MAIN-LOGIC. * Check current line position MOVE LINE-COUNTER TO CURRENT-LINE * Determine if page break is needed IF CURRENT-LINE >= FOOTER-START PERFORM FORCE-PAGE-BREAK END-IF * Check if we're at the top of a page IF CURRENT-LINE <= HEADER-LINES PERFORM WRITE-HEADER END-IF STOP RUN. FORCE-PAGE-BREAK. * Force a page break WRITE REPORT-LINE FROM SPACES * This will cause LINE-COUNTER to reset to 1 DISPLAY "Page break occurred, LINE-COUNTER reset to: " LINE-COUNTER. WRITE-HEADER. * Write header information DISPLAY "Writing header at line: " LINE-COUNTER * Write header content here.
Page break management uses LINE-COUNTER to determine when to start new pages.
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647* Conditional formatting based on LINE-COUNTER IDENTIFICATION DIVISION. PROGRAM-ID. CONDITIONAL-FORMATTER. DATA DIVISION. WORKING-STORAGE SECTION. 01 FORMAT-TYPE PIC X(10). 01 LINE-POSITION PIC 9(2). PROCEDURE DIVISION. MAIN-LOGIC. * Get current line position MOVE LINE-COUNTER TO LINE-POSITION * Apply conditional formatting based on line position EVALUATE LINE-POSITION WHEN 1 MOVE "HEADER" TO FORMAT-TYPE PERFORM APPLY-HEADER-FORMAT WHEN 2 THRU 5 MOVE "SUBHEADER" TO FORMAT-TYPE PERFORM APPLY-SUBHEADER-FORMAT WHEN 55 THRU 60 MOVE "FOOTER" TO FORMAT-TYPE PERFORM APPLY-FOOTER-FORMAT WHEN OTHER MOVE "BODY" TO FORMAT-TYPE PERFORM APPLY-BODY-FORMAT END-EVALUATE STOP RUN. APPLY-HEADER-FORMAT. * Apply header formatting DISPLAY "Applying header format at line: " LINE-COUNTER. APPLY-SUBHEADER-FORMAT. * Apply subheader formatting DISPLAY "Applying subheader format at line: " LINE-COUNTER. APPLY-FOOTER-FORMAT. * Apply footer formatting DISPLAY "Applying footer format at line: " LINE-COUNTER. APPLY-BODY-FORMAT. * Apply body formatting DISPLAY "Applying body format at line: " LINE-COUNTER.
Conditional formatting uses LINE-COUNTER to apply different styles based on line position.
Following these best practices ensures effective use of LINE-COUNTER in COBOL applications.
Page Type | LINAGE Configuration | Use Case |
---|---|---|
Standard Report | 66 LINES, FOOTING AT 60 | Business reports |
Compact Report | 50 LINES, FOOTING AT 45 | Dense data reports |
Detailed Report | 80 LINES, FOOTING AT 75 | Detailed analysis reports |
Letter Format | 60 LINES, FOOTING AT 55 | Letter-style documents |
Invoice Format | 40 LINES, FOOTING AT 35 | Invoice and billing documents |
Use Case | LINE-COUNTER Suitability | Reasoning |
---|---|---|
Report generation | Excellent | Essential for proper page formatting |
Page break management | Excellent | Automatic page break handling |
Header/footer positioning | Excellent | Precise positioning control |
Data processing | Poor | Not designed for data processing |
File operations | Poor | Not designed for file operations |
Operation | Syntax | Example |
---|---|---|
Check current line | IF LINE-COUNTER condition | IF LINE-COUNTER > 50 |
Page break check | IF LINE-COUNTER >= footer-line | IF LINE-COUNTER >= 55 |
Header positioning | IF LINE-COUNTER = 1 | IF LINE-COUNTER = 1 |
Footer positioning | IF LINE-COUNTER = footer-line | IF LINE-COUNTER = 55 |
Display current line | DISPLAY LINE-COUNTER | DISPLAY "Line: " LINE-COUNTER |
1. What is the primary purpose of the LINE-COUNTER special register in COBOL?
2. How is LINE-COUNTER typically used in COBOL programs?
3. What happens to LINE-COUNTER when a page break occurs?
4. Which COBOL clause is most closely related to LINE-COUNTER?
5. How do you access the current value of LINE-COUNTER in a COBOL program?
Understanding the LINAGE clause for page formatting.
Understanding LINAGE-COUNTER for page management.
Complete guide to report generation in COBOL.
Using LINE-COUNTER with file descriptions.
Advanced page formatting techniques.