Compaq COBOL
Reference Manual


Previous Contents Index

1.2.3 Figurative Constants

Figurative constants name and refer to specific constant values generated by the compiler. The singular and plural forms of figurative constants are equivalent and interchangeable. Table 1-8 lists the figurative constants.

Table 1-8 Figurative Constants
Figurative Constant Value
ZERO, ZEROS, ZEROES Represent the value zero, or one or more occurrences of the character 0 from the computer character set, depending on context. In the following example, the first use of the word ZERO represents a zero value; the second represents six 0 characters:
03 ABC PIC 9(5) VALUE ZERO.

03 DEF PIC X(6) VALUE ZERO.
SPACE, SPACES Represent one or more space characters from the computer character set.
HIGH-VALUE,
HIGH-VALUES
Represent one or more occurrences of the character with the highest ordinal position in the program collating sequence. For example, HIGH-VALUE for the native collating sequence is hexadecimal FF.

The value of HIGH-VALUE depends on the collating sequence specified by clauses in the OBJECT-COMPUTER and SPECIAL-NAMES paragraphs. For example, if the program collating sequence is ASCII, HIGH-VALUE is hexadecimal 7F (hexadecimal FF for EBCDIC). For more information, see Section 4.1.2 and Section 4.1.3 sections in Chapter 4, Environment Division.

LOW-VALUE,
LOW-VALUES
Represent one or more occurrences of the character with the lowest ordinal position in the program collating sequence (hexadecimal 00 for the native collating sequence).

The value of LOW-VALUE depends on the program collating sequence specified by clauses in the OBJECT-COMPUTER and SPECIAL-NAMES paragraphs. For more information, see the Section 4.1.2 and Section 4.1.3 sections in Chapter 4, Environment Division.

QUOTE, QUOTES Represent one or more occurrences of the quotation mark character. QUOTE or QUOTES cannot be used in place of a quotation mark to bound a nonnumeric literal. The following examples are not equivalent:
QUOTE abcd QUOTE

"abcd"
ALL Literal Represents one or more occurrences of the string of characters making up the literal. The literal must be either nonnumeric, a symbolic-character, or a figurative constant other than ALL literal. For a figurative constant, the word ALL is redundant and serves only to enhance readability. 1
Symbolic-character Represents one or more occurrences of the character specified as the value of symbolic-character. (See Section 4.1.3 in Chapter 4, Environment Division.)


1The reserved word ALL, not followed by a literal, can be a subscript of an identifier that is a function argument. (The function must allow a variable number of arguments in this argument position; see Chapter 7.)

When a figurative constant represents a string of one or more characters, the string's length depends on its context:

A figurative constant is valid wherever the word literal (or its abbreviation, "lit") appears in a general format or its associated rules. However, ZERO (ZEROS or ZEROES, plural) is the only valid figurative constant for literals restricted to numeric characters.

The actual characters associated with HIGH-VALUE, HIGH-VALUES, LOW-VALUE, and LOW-VALUES depend on the program collating sequence. For more information, see Section 4.1.2 and Section 4.1.3 in Chapter 4, Environment Division.

1.2.4 PICTURE Character-Strings

A PICTURE character-string defines the size and category of an elementary data item. It can consist of the currency symbol ($) and certain combinations of characters in the COBOL character set. (See Section 5.3.37.)

A punctuation character that is part of a PICTURE character-string is not considered to be a punctuation character. Instead, the compiler treats it as a symbol within the PICTURE character-string.

1.2.5 Separators

A separator delimits character-strings. It can be one character or two contiguous characters formed according to the rules in Table 1-9.

Table 1-9 Separators
Separator Usage Rules
Space The space can be a separator or part of a separator.
  • Where a space is used as a separator or part of a separator, more than one space can be used.
  • A space can immediately precede any separator except:
    • As specified by the rules for reference formats (see Section 1.3)
    • The closing quotation mark of a nonnumeric literal; the space is then considered part of the nonnumeric literal rather than a separator
  • A space can immediately follow any separator except the opening quotation mark of a nonnumeric literal. After an opening quotation mark, the space is considered part of the nonnumeric literal rather than a separator.
Comma and Semicolon The comma and semicolon are separators when they immediately precede a space. In this case, the comma and semicolon are interchangeable with each other and with the separator space. They can be used anywhere in a source program that a separator space can be used.
Period The period is a separator when it immediately precedes a space or a return character. It can be used only where allowed by:
Parentheses Parentheses can be used only in balanced pairs of left and right parentheses to delimit:
  • Subscripts
  • Indexes
  • Arithmetic expressions
  • Conditions
  • Reference modification
  • Boolean expressions
  • Intrinsic function argument lists
Quotation Marks
Apostrophes
An opening quotation mark or apostrophe must be immediately preceded by a separator space or a left parenthesis. A closing quotation mark (") or apostrophe (') must be immediately followed by one of the separators: space, comma, semicolon, period, or right parenthesis.
Horizontal Tab The horizontal tab aligns statements or clauses on successive columns of the source program listing. It is interchangeable with the separator space. When the compiler detects a tab character (other than in a nonnumeric literal), it generates one or more space characters consistent with the tab character position in the source line. (See Section 1.3.)
Pseudo-Text
Delimiter
The pseudo-text delimiter is two contiguous equal signs (==), both of which must be on the same source line. A space must immediately precede an opening pseudo-text delimiter. One of the following separators must immediately follow a closing pseudo-text delimiter: spaces, commas, semicolons, or periods.

Pseudo-text delimiters can be used only in balanced pairs. They delimit pseudo-text. (See Chapter 8.)

Colon The separator colon delimits operands in reference modification. It is required when shown in a general format. (See Section 6.2.3.)

1.3 Source Reference Format

The Compaq COBOL compiler recognizes two source program formats: ANSI and terminal.

By default, the compiler expects terminal-format source lines. The compiler expects ANSI format only when the command line includes the ansi compiler option.

The reference format rules for spacing take precedence over all other spacing rules.

1.3.1 ANSI Format

The ANSI source reference format describes COBOL programs in terms of character positions on an input line. A source program line has 80 character positions as shown in Figure 1-1.

Figure 1-1 Source Program Line


Margin L

Immediately to the left of the leftmost character position.

Margin C

Between character positions 6 and 7.

Margin A

Between character positions 7 and 8.

Margin B

Between character positions 11 and 12.

Margin R

Between character positions 72 and 73.

Sequence Number Area

The six character positions between Margin L and Margin C. The contents can be any characters from the computer character set.

The compiler does not check the uniqueness of the contents. However, the compiler does check for the ascending sequence of the contents if the compiler command line includes the sequence compiler option.

Indicator Area

The seventh character position. The character in this position directs the compiler to interpret the source line in one of the following ways:
Character Source Line Interpretation
space ( ) Default. The compiler processes the line as normal COBOL text.
hyphen (-) Continuation line. The compiler processes the line as a continuation of the previous source line.
asterisk (*) Comment line. The compiler ignores the contents of the line. However, the source line appears on the program listing.
slash (/) New listing page. The compiler treats the line as a comment line. However, it advances the program listing to the top of the next page before printing the line.
A-Z, a-z Conditional compilation lines. The compiler processes the line as normal COBOL text if you specify the DEBUGGING MODE clause in the SOURCE-COMPUTER paragraph, or if you specify the conditionals compiler option in the command line. If you do not specify either, the compiler processes this line as a comment line.

Area A

The four character positions between Margin A and Margin B. Area A contains division headers, section headers, paragraph headers, paragraph-names, level indicators, and certain level-numbers.

Area B

The 61 character positions between Margin B and Margin R. Area B contains all other COBOL text.

Identification Area

The eight character positions immediately following Margin R. The compiler ignores the contents of the identification area. However, the contents appear on the source program listing.

Line Continuation

Sentences, entries, phrases, and clauses that continue in Area B of subsequent lines are called continuation lines. The line being continued is called the continued line.

A hyphen in a line's indicator area causes its first nonblank character in Area B to be the immediate successor of the last nonblank character of the preceding line. This continuation excludes intervening comment lines and blank lines.

However, if the continued line ends with a nonnumeric literal without a closing quotation mark, the first nonblank character in Area B of the continuation line must be a quotation mark. The continuation starts with the character immediately after the quotation mark. All spaces at the end of the continued line are part of the literal. Area A of the continuation line must be blank.

If the indicator area is blank:

ANSI Format Example


001010 01  NUMERIC-CONTINUATION. 
001020     03  NUMERIC-LITERAL          PIC  9(16) VALUE IS 123 
001030-    4567890123456. 
001040 01  NONNUMERIC-CONTINUATION. 
001050     03  NONNUMERIC-LITERAL       PIC  X(40) VALUE IS "AB 
001060-    "CDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmn". 
001070 PROCEDURE DIVISION. 
001080 SENTENCE-CONTINUATION. 
001090     IF NUMERIC-LITERAL NOT = SPACES 
001100         DISPLAY "NUMERIC-LITERAL NOT = SPACES" 
001110     ELSE 
001120         DISPLAY NUMERIC-LITERAL. 

Lines 001020 and 001030 show continuation of a numeric literal. Lines 001050 and 001060 continue a nonnumeric literal. A sentence that spans four lines begins on line 001090.

Blank Lines

A blank line contains no characters other than spaces between Margin C and Margin R. Blank lines can be anywhere in a source program or library text.

Comment Lines

A comment line is any source line with an asterisk (*) or slash (/) in its indicator area. Area A and Area B can contain any characters from the computer character set. Comment lines can be anywhere in a source program or library text.

Conditional Compilation Lines

A conditional compilation line is any source line after the OBJECT COMPUTER paragraph that includes one of these uppercase or lowercase alphabetic characters in its indicator area: A to Z, a to z. The compiler processes the line as normal COBOL text if you specify the DEBUGGING MODE clause in the SOURCE COMPUTER paragraph.

The compiler processes the line as normal COBOL text if you include the appropriate conditionals compiler option in the command line.

If you specify neither, the compiler processes this line as a comment line.

Lines conditioned by one letter can be compiled or treated as comments independently of other conditional compilation lines. On OpenVMS Alpha systems, for instance, if you compile with /CONDITIONALS=(A,B), lines conditioned with A and B compile while those conditioned by other letters are treated as comments.

See Chapter 8 for additional information on the interaction between conditional compilation lines and the COPY statement.

Pseudo-Text

Pseudo-text character-strings and separators can start in either Area A or Area B. However, if there is a hyphen in the indicator area of a line that follows the opening pseudo-text delimiter, Area A of the line must be blank.

The normal rules for line continuation apply to the formation of text-words.

Pseudo-text is described in Chapter 8.

Short Lines and Tab Characters

If the source program input medium is not punched cards, carriage return and horizontal tab characters can shorten source lines.

The compiler recognizes the end of the input line as Margin R. Tab characters, other than those in nonnumeric literals, cause the compiler to generate enough space characters to position the next character at the next tab stop. The compiler's tab stops are at character positions 8, 12, 20, 28, 36, 44, 52, 60, 68, and 76.

The following example shows how the compiler interprets carriage return and horizontal tab characters in a source program:

Shortened ANSI Format Source Line


000100*The following record description shows the source line format[Return]
000110 01[Tab]RECORD-A.[Return]
000120[Tab][Tab]03  GROUP-A.[Return]
000130[Tab][Tab][Tab]05  ITEM-A[Tab]PIC X(10).[Return]
000140*[Tab]The tab character in the nonnumeric literal[Return]
000150*[Tab]on the next line is stored as one character[Return]
000160[Tab][Tab][Tab]05  
ITEM-B[Tab]PIC X VALUE IS "[Tab]".[Return]
000170[Tab][Tab]03  ITEM-C[Tab][Tab]PIC X(10).[Return]
000180D01[Tab]RECB REDEFINES RECORD-A[Tab]PIC X(21).[Return]

Source Line as Interpreted by the Compiler


000100*The following record description shows the source line format 
000110 01  RECORD-A. 
000120     03  GROUP-A. 
000130             05  ITEM-A      PIC X(10). 
000140*    The tab character in the nonnumeric literal 
000150*    on the next line is stored as one character 
000160             05  ITEM-B      PIC X VALUE IS "[Tab]". 
000170     03  ITEM-C              PIC X(10). 
000180D01  RECB REDEFINES RECORD-A PIC X(21). 

Use more tab characters only when necessary. Compiler error diagnostics result if you use tab characters beyond the permissible character positions for a COBOL statement or entry. The following example shows how the compiler treats source program lines 000004 and 000005. Line 000004: contains one too many tab characters, which places paragraph-name P0 out of Area A.

Shortened ANSI Format Source Line


000001[Tab]IDENTIFICATION DIVISION. 
000002[Tab]PROGRAM-ID. ANSI-TEST. 
000003[Tab]PROCEDURE DIVISION. 
000004[Tab][Tab]P0. 
000005[Tab][Tab]STOP RUN. 

Listing File Result on OpenVMS


000001 IDENTIFICATION DIVISION. 
000002 PROGRAM-ID. ANSI-TEST. 
000003 PROCEDURE DIVISION. 
000004   P0. 
.........^ 
%COBOL-F-UNDEFSYM, Undefined name 
at line number 4 in file DISK:[DIRECTORY]ANSI.COB;1 
 
000005  STOP RUN. 
........^ 
%COBOL-W-SYN6, Missing paragraph header 
at line number 5 in file DISK:[DIRECTORY]ANSI.COB;1  <>
 

Listing File Result on Tru64 UNIX


000001 IDENTIFICATION DIVISION. 
000002 PROGRAM-ID. ANSI-TEST. 
000003 PROCEDURE DIVISION. 
cobol: Severe: dwork/t.cob, line 4: Undefined name 
000004  P0. 
--------^ 
cobol: Warning: dwork/t.cob, line 5: Missing paragraph header 
000005  STOP RUN.  <>
--------^ 
 

Listing File Result on Windows NT


AAA.COB(5) : Severe: Undefined name 
000004  P0. 
--------^ 
AAA.COB(6) : Warning: Missing paragraph header 
000005  STOP RUN.  <>
--------^          

Note

The previous error messages have no additional online explanations. If a diagnostic message has a further explanation, an asterisk (*) is displayed (to the left of the error message). On OpenVMS Alpha systems, the Compaq COBOL online Help file lists and describes error messages that have further explanations.

1.3.2 Terminal Format

The Compaq COBOL terminal format shortens program preparation time and reduces storage space for source programs. This format eliminates the sequence number and identification areas. It also combines the indicator area with Area A. Except for the differences described in this section, the rules for ANSI format also apply to terminal-format source programs.

In terminal format, the compiler recognizes the following valid indicator area characters in the first character position:

(-) hyphen
(*) asterisk
(/) slash

The compiler also recognizes the following conditional compilation line characters as valid indicator area characters in the first and second character positions:

(\x) backslash and x

where x can be any uppercase or lowercase alphabetic character.

Area A then begins in character position 2 (or 3 if using \x). Otherwise, Area A begins in the first character position.

Area B begins four character positions to the right of the beginning of Area A. It ends when the compiler detects a carriage return, or at Margin R.

The maximum length of a terminal-format source line is 256 characters. The compiler's tab stops are immediately to the right of Margin B, and every eight character positions to the right, until the end of the line.

Note

The maximum length of the source line on the program listing is 125 characters, including the sequence field. The compiler processes the complete source line but displays only the first 125 characters on the listing. It also replaces all nonprintable ASCII characters with periods (or other symbols depending on the device) in the listing file. (Refer to the Compaq COBOL User Manual.

The following example shows source lines in terminal format. It is equivalent to the ANSI-format source line examples in the previous section.


*The following record description shows the source line format[Return]
01[Tab]RECORD-A.[Return]
[Tab]03  GROUP-A.[Return]
[Tab][Tab]05  ITEM-A[Tab]PIC X(10).[Return]
*[Tab]The tab character in the nonnumeric literal[Return]
*[Tab]on the next line is stored as one character[Return]
[Tab][Tab]05  ITEM-B[Tab]PIC X VALUE IS "[Tab]".[Return]
[Tab]03  ITEM-C[Tab][Tab]PIC X(10).[Return]
\D01[Tab]RECB REDEFINES RECORD-A[Tab]PIC X(21).[Return]


Previous Next Contents Index