Your Browser is not longer supported

Please use Google Chrome, Mozilla Firefox or Microsoft Edge to view the page correctly
Loading...

{{viewport.spaceProperty.prod}}

Format control statements TITLE, EJECT, SKIP

The COBOL2000 compiler supports the format control statements TITLE, EJECT and SKIP. These statements can be used in the compiler unit to control the format of the source listing. Format control statements are governed by the following rules:

  • They must not be concluded with a period.

  • They must be contained exclusive in a line from column 12.

  • They themselves do not appear in the source listing.

TITLE statement

Function

This statement is used to print the specified title instead of the standard title (SOURCE LISTING) in the header lines of the source listing that follow. In addition, a page feed is performed unless a new page was to be started anyway.

Format


TITLE literal

Rule

literal must be a non-numeric literal of up to 53 characters.

EJECT statement

Function

This statement causes the following text of the source listing to begin at the top of the next page. This statement has no effect if a new page was to be started anyway.

Format


EJECT

SKIP statement

Function

The SKIP statement is used to shift the following text by up to three lines. The statement has no effect if blank lines would be the first to appear at the top of the next page.

Format


{SKIP1}
{SKIP2}
{SKIP3}

Example 17-1

Format control statements

IDENTIFICATION DIVISION.
PROGRAM-ID. EXAMPLE.
DATA DIVISION.
    TITLE "WORKING-STORAGE SECTION" —————————————(1) 
WORKING-STORAGE SECTION.
01 ALPHA1 PIC 99 VALUE 1.
01 BETA1 PIC 99 VALUE 2.
01 GAMMA1 PIC 99.
    TITLE "PROCEDURE DIVISION"———————————————————(2) 
PROCEDURE DIVISION.
    EJECT ———————————————————————————————————————(3) 
BEGIN SECTION.
MULT.
    MULTIPLY ALPHA1 BY BETA1 GIVING GAMMA1.
    MULTIPLY BETA1 BY GAMMA1 GIVING ALPHA1.
    MULTIPLY GAMMA1 BY ALPHA1 GIVING BETA1.
    SKIP3 ———————————————————————————————————————(4) 
 END SECTION.
 STOPP.
     STOP RUN.

Effect:

(1)

The header line of the next page of the source listing will read: “WORKING-STORAGE SECTION”

(2)

The header line of the next page(s) of the source listing will read: “PROCEDURE DIVISION”.

(3)

The following text to be printed (BEGIN SECTION...) will begin on a new page.

(4)

The following text to be printed (END SECTION) will be preceded by three blank lines.